Skip to content

Types#

Discrete Types#

Numbers have a set of universal types that are not language types, but are compile-time concepts that are then converted to a definite type. TODO

Relevant Attributes
Attribute Description
X'Pred The next value in the type’s sequence
X'Succ The previous value in the type’s sequence
X'First The smallest/first value
X'Last The largest/last value
X'Size The number of bits required to represent the type
T'Base The underlying type based on the machine sizes
X'Range The range of the type
T'Mod Convert any integer to a modular type

Integers#

The universal types for integers are referred to as universal_integer and root_integer.

Signed Integers#

Built-in Types
  • Integer, Short_Integer, Long_Integer
  • Integer_8, Integer_16, Integer_32, Integer_64 and Integer_128

Note that of these types, only Integer is required to be defined. Others are optional and may vary either by choice or by hardware limitations.

The basic integer type is Integer and there may additionally be Short_Integer and Long_Integer. These types, as in C, are not precisely sized and vary based on the machine. The type Integer must always exist with at least 16 bit range and Long_Integer (if it is defined) must have at least a 32 bit range.

-- Using learn.adacore.com, the machine uses twos-complement integers with 16-, 32-
-- and 64-bit integers for Short_Integer, Integer and Long_Integer respectively.
Put_Line(Integer'Image(Integer'First)); -- -2 147,483,648 
Put_Line(Integer'Image(Integer'Last));  --  2 147,483,647
Put_Line(Integer'Image(Integer'Size));  --  32

Put_Line(Short_Integer'Image(Short_Integer'First)); -- -32,768
Put_Line(Short_Integer'Image(Short_Integer'Last));  --  32,767
Put_Line(Short_Integer'Image(Short_Integer'Size));  --  16

Put_Line(Long_Integer'Image(Long_Integer'First)); -- -9 223,372,036,854,775,808
Put_Line(Long_Integer'Image(Long_Integer'Last));  --  9 223,372,036,854,775,807
Put_Line(Long_Integer'Image(Long_Integer'Size));  --  64
When a specific range of values is required, you can (and generally should) specify the range of a type. Defining integers as ranges allows the compiler to select the smallest size of machine integer in which the integer fits. The hardware type may be accessed with 'Base and all the operations are done with the idea that the parameters are of the type My_Integer'Base.
type My_Integer is range -1E6 .. 1E6;
-- My_Integer'Range = -1E6 .. 1E6
-- My_Integer'Base  = -2**31 .. 2**31 - 1

Put_Line(My_Integer'Image(My_Integer'First)); -- -1 000,000
Put_Line(My_Integer'Image(My_Integer'Last));  --  1 000,000
Put_Line(My_Integer'Image(My_Integer'Size));  --  21

A_32_Bit_Integer: My_Integer'Base;
On standard systems today, My_Integer would be stored in a 32-bit integer, but a machine with 12-bit bytes, for example, may allow it to be stored in a 24-bit integer. Only multiples of 8 will be considered here. All the types (regardless of the exact implementation) may be thought of as defined via a root integer type with the range System.Int_Min .. System.Int_Max.

Overflow checks are done to ensure that the correct mathematical result is achieved or a Constraint_Error is raised. Constraint checks are done differently in that they take place on assignment. Take, for example:

X: Some_Integer := 250;
Y: Some_Integer := X*X / 1000;
In the case that the X*X is done using an underlying 16-bit hardware integer, it will overflow and cause a Constraint_Error. If instead it is done with a 32-bit hardware integer, it will not overflow and, although Some_Integer may have its bounds exceeded temporarily, a range check for Some_Integer will only be done on assignment where it is no longer out-of-bounds after the division by 1000.

Unsigned Integers#

Built-in Types
  • Unsigned_8, Unsigned_16, Unsigned_32, Unsigned_64, Unsigned_128

Unsigned integers are known as modular types because they exhibit cyclic arithmetic. The attribute 'Mod may be used in order to convert an integer to a modular type.

type Degrees is mod 360; -- Valid values are 0 .. 359
Standard operations are available for modular types as for signed integer types, but note that the not operation subtracts the current value from the maximum as you would expect for a power-of-two mod value ((not Degrees'(30)) = Degrees'(329)).

For the built-in modular types, the subprograms Shift_Left, Shift_Right, Shift_Right_Arithmetic, Rotate_Left and Rotate_Right are defined and all have the same signature of:

function Shift_Left(Value: Unsigned_16; Amount: Natural) return Unsigned_16;

Real Numbers#

Real numbers are divided into two types: floating point and fixed point. Fixed point are further divided into ordinary fixed point and decimals. The main difference between the two (apart from their implementations) is that floating point have relative errors, but fixed point have absolute errors. The universal types are referred to as universal_real and root_real like the integer equivalents.

Floating-Point#

Implementations have a type Float and may have Short_Float and Long_Float. The type Float should have at least 6 digits of precision and Long_Float (if available) should have at least 11 digits of precision. The package Interfaces will (if available) define IEEE_Float_32 and IEEE_Float_64.

-- Using learn.adacore.com, both Float and Short_Float are 32-bit floats
-- while Long_Float is a 64-bit float.
Put_Line(Float'Image(Float'First));   -- -3.40282E+38
Put_Line(Float'Image(Float'Last));    --  3.40282E+38
Put_Line(Integer'Image(Float'Size));  --  32

Put_Line(Short_Float'Image(Short_Float'First)); -- -3.40282E+38  
Put_Line(Short_Float'Image(Short_Float'Last));  --  3.40282E+38  
Put_Line(Integer'Image(Short_Float'Size));      --  32

Put_Line(Long_Float'Image(Long_Float'First)); -- -1.79769313486232E+308 
Put_Line(Long_Float'Image(Long_Float'Last));  --  1.79769313486232E+308 
Put_Line(Integer'Image(Long_Float'Size));     --  64
For portability, it is best no to use the predefined package types and to define types if the default Float and Long_Float are not suitable. type My_Float is digits 9; requests that the type has at least 9 digits of precision, but likely has more based on the hardware representation chosen by the implementation. Because the precision might not hold constantly over the whole range, a guaranteed safety range is provided for \([-10.0^{4D}, +10.0^{4D}]\). The only resulting effect that limiting the number of digits (while under the same hardware representation) will have is that the default output format will be truncated.

Constrained floating point types also work, but the \(4D\) rule no longer applies.

type Chance is digits 6 range 0.0 .. 1.0;

Relevant Attributes
Value Attributes Machine Attributes Model Attributes
S'Exponent S'Machine_Emin S'Model
S'Fraction S'Machine_Emax S'Model_Epsilon
S'Adjacent S'Machine_Radix S'Model_Small
S'Ceiling S'Machine_Mantissa S'Model_Mantissa
S'Compose S'Machine_Overflows S'Model_Emin
S'Floor
S'Leading_Part S'Signed_Zeros
S'Machine_Rounding S'Digits
S'Remainder S'First
S'Rounding S'Last
S'Scaling S'Safe_First
S'Truncation S'Safe_Last
S'Unbiased_Rounding
S'Copy_Sign

Remember that the underlying type can be accessed via the S'Base attribute. The canonical floating-point model is: \(\operatorname{sign} \cdot \operatorname{mantissa} \cdot \operatorname{radix}^{\operatorname{exponent}}\).

Enumerations#

type Day is (Monday, Tuesday, Wednesday, Thursday, Friday, Saturday, Sunday);
subtype Weekday is (Day range Monday .. Friday);

type Month_Name is (Jan, Feb, Mar, Apr, May, Jun,
                    Jul, Aug, Sep, Oct, Nov, Dec);

type Boolean is (False, True);

Ranges#

I in 2 | 4 | 6
I in 1 .. 10
I in 1 .. 10 | 90 .. 100
I not in 7 .. 11
I in Positive -- range types

D in Jan .. June
D in Feb | June | Nov
D not in Jan .. May | Oct .. Dec
D in Weekday -- enumeration types

C in 'a' | 'e' | 'i' | 'o' | 'u'

Object in Triangle | Rectangle -- tagged types

Types with Dynamic Predicates

Subtypes checks may have dynamic predicates and so in checks have the potential to raise an exception in such a case (depending on the definition of the predicates).

Arrays#

Array types are limited if its component type is limited.

As of Ada2022, array literals may use brackets.

My_Array   : array(Integer range 1 .. 5) of Float;
My_2D_Array: array(0 .. 2, 0 .. 2) of Float;
Enum_Array : array(Day) of Integer;

My_Array    := (1.0, 2.0, 3.0, 4.0, 5.0);
My_2D_Array := ((1.0, 2.0, 3.0), (4.0, 5.0, 6.0), (7.0, 8.0, 9.0));
Enum_Array  := (2, 3, 4, 5, 6, 7, 1)

type Unconstrained_Array is array(Positive range <>) of Boolean;
subtype Constrained_Array is Unconstrained_Array(1 .. 10);

type Array_With_Default is array(Integer range <>) of Integer
   with Default_Component_Value => 1;

Indexing#

My_Array(1)      = 1.0
My_Array(2 .. 3) = (2.0, 3.0)

My_2D_Array(0, 1)      = 2.0
My_2D_Array(1, 1 .. 2) = (5.0, 6.0)

My_2D_Array'Last(0) = 7.0

My_Array(1 .. 5) := 0.0;                      -- (0.0, 0.0, 0.0, 0.0, 0.0)
My_Array := (1 .. 3 => 1.0, others => 0.0)    -- (1.0, 1.0, 1.0, 0.0, 0.0)
My_Array := (1 | 3 | 5 => 2.0, others => 0.0) -- (2.0, 0.0, 2.0, 0.0, 2.0)

Default_Array: Array_With_Default(1 .. 3) := (others => <>); -- Set all to default value

-- Bounds can be inferred via aggregates
Array_1: array(Weekday range <>) of Day := (Monday, Thursday);
Array_2: Unconstrained_Array := (True, True, False);

Arrays have sliding semantics that allow for mismatching ranges to work. This means an array with range 1 .. 3 and another with range 0 .. 2 can be considered equivalent. This can often be useful with slices such as: An_Array(1 .. 3) and Another_Array(7 .. 9).

Multi-dimensional arrays can function in two ways:

type Vector_3 is array(1 .. 3) of Float;
type Matrix_3X3 is array(1 .. 3) of Vector_3;
type Matrix_2D_3X3 is array(1 .. 3, 1 .. 3) of Float;
Indexing then differs as Matrix_3X3(I)(J) and Matrix_2D_3X3(I, J) and the array-of-arrays has the benefit of accessing multiple elements by slice: Matrix_3X3(2) := (1 .. 3 => 0.0);.

Iteration#

for N in Enum_Array loop
    Put_Line(Integer'Image(N));
end loop;

for I in My_2D_Array'Range(1) loop
    for J in My_2D_Array'Range(2) loop
        AA(I, J) := 0.0;
    end loop;
end loop;

The range value does not have to be static, you can for example do: (Integer range 1 .. N)

Operations#

Due to the different character types, comparisons may often be invalid as the type of the literal is not known:

-- Illegal
"CAT" < "DOG"
"CCL" < "CCXC"

Wide_String'("CAT") < "DOG"   -- True
String'("CCL") < "CCXC"       -- True
Roman_Number'("CCL") < "CCXC" -- False

The operators <, <=, > and >= can be applied to one dimensional arrays:

type Array_Type is array(1 .. 3) of Integer;
A: Array_Type := (1, 2, 3);
B: Array_Type := (4, 5, 6);
A < B = True

Note that the following is illegal:

A: array(1 .. 3) of Integer := (1, 2, 3);
B: array(1 .. 3) of Integer := (4, 5, 6);
A < B -- Illegal

The operators and, or, xor and not can be applied to one dimensional boolean arrays:

XX, YY: array(1 .. 4) of Boolean;
XX := (1, 3 => True, others => False);   -- (True, False, True, False)
YY := (1 .. 2 => True, 3 .. 4 => False); -- (True, True, False, False)

XX := XX and YY; -- XX = (True, False, False, False)
XX := not XX;    -- XX = (False, True, True, True)

Aggregates#

This section is only for the Ada2022 standard.

Ada has the ability to create arrays in a list comprehension style. There are three different versions: construction comprehensions, filters and deltas. Construction comprehensions are used to build an array from scratch. Filter comprehensions are used to create an array by picking values from an existing array. Deltas are used to create an array from an existing array with certain changes.

Even_Numbers: array(1 .. 100) of Integer := [for I in 1 .. 100 => 2*I];
Matrix_3X3_Ident: Matrix_3X3 := [
   for J in 1 .. 3 =>
      [for I in 1 .. 3 => (if I = J then 1.0 else 0.0)]
];
Flat_Matrix_3X3_Ident: array(1 .. 9) of Float := [
   for D in 1 | 5 | 9 => 1.0,
   others => 0.0
];

-- Filters
Filter_Aggregate: array(Positive range <>) of Float := [
   for E of Flat_Matrix_3X3_Ident
      when E = 1.0 => E
];

-- Deltas
Date_Record : Date := (10, Jan, 2000);
Delta_Record: Date := (Date_Record with delta Day => 15, Month => Feb);

Records#

type Date is record
   Day  : Integer range 1 .. 31;
   Month: Month_Name;
   Year : Integer;
end record;

A_Date: Date
A_Date.Day   := 7;
A_Date.Month := Dec;
A_Date.Year  := 2020;

A_Date_2: Date := (Day => 10, Month => Jan, Year => 2017);
A_Date_3: Date := (10, Jan, 2017);

type Complex is record
   Real: Float := 0.0;
   Imag: Float := 0.0;
end record;

Complex_Num: Complex;                          -- (Real => 0.0, Imag => 0.0)
Complex_Num2: Complex := (Real | Imag => 0.5); -- (Real => 0.5, Imag => 0.5)
Complex_Num3: Complex := (others => 1.0);      -- (Real => 1.0, Imag => 1.0)
Complex_Num4: Complex := (others => <>);       -- (Real => 0.0, Imag => 0.0)
The only operations that are defined by default on records are those of =, /= and := (equality, inequality and assignment).

Ada2022

end record; may also contain the name of the record being ended, such as end record Complex; or end record Date;.

Strings#

Strings in Ada are arrays of type Character, Wide_Character or Wide_Wide_Character. From this, there are three basic types of strings: String, Wide_String and Wide_Wide_String.

type String           is array(Positive range <>) of Character;
type Wide_String      is array(Positive range <>) of Wide_Character;
type Wide_Wide_String is array(Positive range <>) of Wide_Wide_Character;

Ada_String_Array  : constant String := ('A', 'd', 'a');
Ada_String_Literal: constant String := "Ada";
Concatenation is performed with the & operator:
"123" & '4' = "1234"
'a' & 'b' = "ab"
"abc" & "DEF" = "abcDEF"

"Can be used for a" &
"multi-line string"

Characters#

The predefined types Character, Wide_Character and Wide_Wide_Character correspond to an enumeration for Latin-1, the Basic Multilingual Plane and the full set of ISO 10646 respectively. The first 256 values of Wide_Character match Character and likewise the first 65536 values of Wide_Wide_Character match Wide_Character.

type Character is (nul, ..., '0', '1', ..., 'A', 'B', ..., 'a', 'b', ..., 'ÿ');
Because strings are arrays of an enumeration type, special strings can be created:
type Roman_Digit is ('I', 'V', 'X', 'L', 'C', 'D', 'M');
type Roman_Numeral is array(Positive range <>) of Roman_Digit;

Fifty_Eight: constant Roman_Numeral := "LVIII";
Four: array(1 .. 2) of Roman_Digit := "IV";

Escape Characters#

('A', '"', 'B') = "A""B"

Common Package Symbols#

with Ada.Text_IO; use Ada.Text_IO;

Put("String");
Put_Line("String");
with Ada.Characters; use Ada.Characters;

Latin_1.CR;
Latin_1.LF;

Access Types#

Access types are Ada’s equivalent for pointer/reference types and they have the default value of null in order to prevent attempted access to undefined memory locations. The attribute 'Access can be used to get the address of a value and may only be applied to variables that are declared as aliased. In order to use get the value pointed to, a field all may be used: My_Access.all (anonymous access types are always general and so do not require the all qualifier). Attempting to use or dereference an access type that is null will result in a Constraint_Error.

A type declared as an access type must include the all qualifier in order to be able to store the access to a general type. Another variation that allows for read-only access is qualifying an access type as constant.

Record fields and array indexing are the same for access types as for the base types.

declare
   type Integer_Access_1 is access Integer;
   type Integer_Access_2 is access all Integer;
   type Constant_Integer_Access is access constant Integer;

   X: Integer;
   Y: aliased Integer;
   Z: aliased constant Integer := 121;
   P: access Integer;

   A: Integer_Access_1;
   B: Integer_Access_2;
   C: Constant_Integer_Access;
begin
   P := X'Access; -- Illegal, X may not be aliased
   P := Y'Access; -- Okay

   A := Y'Access;    -- Illegal, Integer_Access_1 is not marked with "all"
   A := new Integer; -- Okay
   B := Y'Access;    -- Okay

   B := Z'Access; -- Illegal, non-constant access to constant value
   C := Z'Access; -- Okay
   C := Y'Access; -- Okay

   A.all := 77; -- Okay
   B.all := 5;  -- Okay
   C.all := 5;  -- Illegal, the left hand side of assignment is constant
end;
type Node;
type Node_Access is access Node;
type Node is record
   Next: Node_Access;
   Data: Integer;
end record;

-- Or with anonymous access types we just need:
type Node_Anon is record
   Next: access Node_Anon;
   Data: Integer;
end record;

declare
   A_List: Node := (null, 0);
begin
   A_List.Next := new Node'(null, 1); -- or simply `new Node` to get default values
end;
-- A_List = Node'(Next => Node'(Next => null, Data => 1), Data => 0)
-- Access types are copied by access value (pointer) and not by object accessed
declare
   A, B: Node_Access;
   C: Node;
   D: Node_Access;
begin
   A := new Node'(null, 77);
   B := A;
   B.Data := 100; -- A.Data = 100 and B.Data = 100

   C := A.all;   -- C.Data = 100
   C.Data := 77; -- C.Data = 77

   D := new Node'(A.all); -- Initialise D with A's values
end;
The new object created via new is allocated from a storage pool and null is a value that applies universally to all access types to denote an invalid/empty value.

When creating constant access types, the position of the constant determines which aspect is constant:

constant access T          -- Access is immutable; data is mutable
access constant T          -- Access is mutable; data is immutable
constant access constant T -- Both data and access are immutable

Null Exclusion#

Because access types are nullable, they need to be checked for null when they are dereferenced. These checks can be avoided via a non-nullable access type. All variables declared as a non-nullable access type must be assigned an initial value on declaration.

type HW_Device_Access is not null access HW_Device;

subtype Non_Null_Node_Access is not null Node_Access;
-- Or just:
A_Node: not null Node_Access := A;

-- Can also use in subprogram parameters:
procedure Transform_Node(N: in out not null Node_Access);
function New_Node(Value: Integer) return not null Node_Access;

Aliasing#

In order to prevent dangling pointers, the 'Access attribute may only be given to objects whose lifetime is at least that of the access type.

declare
   P: access Integer;
begin
   declare
      X: aliased Integer;
   begin
      P := X'Access; -- error: non-local pointer cannot point to local object
   end;
end;
Another example based on the access’s type is less obvious because it is based on the scope of the type. This is because the access’s value might be copied by a variable in a parent scope and then the invalid access value used. In order to bypass this, Unchecked_Access may be used which will then omit any safety checks.
type Integer_Access is access all Integer;
Outer_P: Integer_Access;
-- ...
declare
   -- Moving the type declaration here removes the error because
   -- then the type cannot be copied and used outside of this scope
   X: aliased Integer;
   P: Integer_Access;
begin
   P := X'Access;           -- error: non-local pointer cannot point to local object
   P := X'Unchecked_Access; -- Okay, but gives no guarantees
   Outer_P := P;            -- Leaks P's value into the outer scope
end;
-- Outer_P's value would no longer be valid

Anonymous Access Types

Another way to avoid this is using anonymous access types (access Integer instead of Integer_Access in this case), but this allows for the issue that Outer_P can be accessed which gives garbage data here. Although anonymous types are more convenient and easier to use, they do not provide the same level of protection from dangling pointers.

Storage Pools#

Access objects that are created reside in space called a storage pool. These pools are typically freed once leaving the scope of the access type. Declaring an access type introduces a new, logically distinct set of accessed objects which may reside in different storage pools.

type Access_A is access all Integer;
type Access_B is access all Integer;
-- These objects might end up in different pools because of the different types
Int_A: Access_A := new Integer'(10);
Int_B: Access_B := new Integer'(20);

Int_A.all := Int_B.all;   -- Okay because the values of the objects are copied
Int_A := Int_B;           -- Illegal because of differing types
Int_A := Access_A(Int_B); -- Okay with an explicit conversion
A type like this without the all qualifier is a pool-specific type because then only objects within its pool would be accessible. Generally, you can convert from pool-specific types to a general or anonymous type, but not in the opposite direction. For pool-specific types:

  • They can only refer to allocated objects and never to aliased, declared objects,
  • They cannot be marked as constant,
  • Conversion between different pool-specific types is forbidden (unless one is derived from the other).

Aliasing#

Ada does not typically define the order of evaluation for expressions in a statement. This is due to historical reasons, but it must be kept in mind with nested expressions. There are no issues for expressions without any side effects, but side effects depending on order of evaluation are illegal.

procedure Increment_Two(First, Second: in out Integer) is
begin
   First  := @ + 1;
   Second := @ + 1;
end Increment_Two;

X, Y: Integer := 0;
Increment_Two(X, X); -- Illegal as `First` and `Second` are overlapping
Increment_Two(X, Y); -- Okay

Renaming#

In Ada2022, Specifying the type of a rename is optional and any named entity may be renamed.

Variables and constants, components of composite objects, exceptions, subprograms and packages may be given another name with renames. This is not the same as a variable definition, but it is like creating a new identifier for the same expression or memory location without doing any copying or pointer aliasing. A similar effect may be had for types via subtype S is T;.

A_String: String := "STRING";
Char_A: Character renames A_String(4); -- Char_A = 'I'
Char_B: Character renames 'q';

Put_Line(A_String); -- STRING
Char_A := 'U';      -- A_String(4) := 'U'
Put_Line(A_String); -- STRUNG

-- Illegal
Char_B := 'w'; -- error: left hand side of assignment must be a variable

-- Subprograms may also be renamed
function Dot(X, Y: Vector) return Float;             -- Needs a body
function "*"(X, Y: Vector) return Float renames Dot; -- Shares Dot's body

Renaming and Constraints

Renaming a subprogram with different constraints via a subtype may be allowed, but the constraints on the original subprogram will be the ones that are applied. Specifically, adding a not null tag to a rename when the original allows null is forbidden because of the false constraint.

Renaming is also not permitted for values of a universal type.

Derived Types#

A type is characterised by a set of values and a set of operations on those values. The basic operations are assignment, equality, applicable attributes and operators such as “+”, “<”, etc. Derived types inherit their basic operations from their parent.

A distinct copy of a type may be created via the new keyword when creating a type: type S is new T;. The type S is a duplicate type that is derived from T which is the parent type. A type with all of the types derived from it form a category of types called a derivation class (or simply a class). All the types in a class share certain properties. An important property is that if the parent is an access type then the derived type will also be an access type and they will share the same storage pool. Although they are different types, conversions between the two types is possible because they have the same underlying data.

Often derived types will inherit too much from its parent. Making in the undesirable subprograms abstract can help.

type Area is new Float;
-- If we don't want to be able to multiply areas
function "*"(Left, Right: Area) return Area is abstract;

Private and Limited Types#

Types in packages may be marked as private in order to hide the implementation of the type and defer its definition. In addition, they may also be limited in order to prevent assignment (copying) and comparison (= and /=). Making a type both private and limited allows the package author great control over the objects in order to prevent misuse. Limited types are always passed by reference.

type T is limited private;
type R is limited record
   -- ...
end record;

Tagged Types#

Package

Record types may be marked as tagged in order to extend them and create a tree of related types. Every tagged type will have either tagged, with or interface and objects will have an implicit tag that may be accessed via the 'Tag attribute (only class-wide types may access the tag). The tag indicates which specific type the object is in the aforementioned tree and can never be changed (although different views of the object may be used). Primitive operations are inherited from the parent similarly to derived types.

type Point is tagged record
   X, Y: Float;
end record;

-- The record section may be `null` to not add any fields.
type Circle is new Point with record
   -- It inherits the `X` and `Y` fields.
   R: Float;
end record;

P : Point  := (0.0, 0.0);
C : Circle := (1.0, 0.0, 2.0);
C2: Circle := (P with 3.0);      -- (0.0, 0.0, 3.0)
C3: Circle := (Point with 2.77); -- (undefined, undefined, 2.77.0)
The example of C3 can have defined values if the Point record is given default values.

To compare tagged types versus derived types: both (1) inherit existing components and primitive operations and (2) may also add additional operations, but:

  • Derivation from a tagged type freezes it so that no more primitive operations may be added.
  • A tagged record may have additional components added to it.
  • Type conversion is only allowed up towards the root of the type hierarchy.

Primitive Operations

Primitive operations are those that are implicitly declared and, in the case of a type declared in a package, all subprograms with a parameter or result of that type.

If you do not want a subprogram to be a primitive operation, it can be placed in a child package. This can prevent types derived from it from inheriting the subprogram.

-- It may explicitly be declared like this without having to create another package.
-- This also allows it to be called in the same way without extra use clauses.
function Parent_Package.Child_Package.My_SR(X: My_Type) return Integer;

Polymorphism#

Each tagged type T has an associated type denoted by the T'Class attribute which denotes the union of all the types derived from T.

flowchart TD
   Point --> Circle --> Cylinder
   Point --> Rectangle

type Point     is tagged record   ...
type Rectangle is new Point  with record ...
type Circle    is new Point  with record ...
type Cylinder  is new Circle with record ...

-- The 'Class attribute may be used as a type
-- and allows for a class-wide access
Val: Point'Class := -- ...
procedure Process(Obj: in out Point'Class);
type Circle_Access is access all Circle'Class;

-- Can test for a value's class
if Val in Rectangle then -- ...
-- or (including derived types
if Val in Rectangle'Class then -- ...
-- or
if Val'Tag = Rectangle'Tag then -- ...
Circle_Access will allow assigning to all inherited types as well (both Circle and Cylinder here). When doing type conversions using tagged types:

  • Conversion between two types is only permitted towards their common parent.
  • Conversion from a specific type to a class-wide type is permitted.
  • Conversion from a class-wide type to a specific type is allowed provided the type is actually descended from the specific type (may need dynamic check).
  • Conversion between two class-wide types is allowed if the actual value is in the target class (may need dynamic check).

The same rules that apply for type conversions also apply for access types to them.

When dispatching, it may be done so either statically or dynamically:

C1, C2: Circle;
X1, X2: Point'Class := -- ... (should be initialised as a class-wide type)
Op(C1, C2); -- Static dispatch for Op(Circle, Circle)
Op(X1, X2); -- Dynamic dispatch with a check that X1'Tag = X2'Tag

Objects may also use dot notation in order to call operations on tagged types with the object being the first parameter of the subprogram. This also avoids any package prefixes that may be required depending on the child package that contains the exact operation definition.

-- For package P and object X
P.Op(X, ...);
X.Op(...);

Abstract Types#

An abstract type may have abstract primitive subprograms which have no bodies and cannot be called but act as placeholders to be added on later. It is also not possible for these reasons to create an object of an abstract type and so not possible for an object to have a tag corresponding to an abstract type.

type T is abstract tagged -- ...
procedure Op_1(X: T) is abstract; -- Must be defined by the children
procedure Op_2(X: T);             -- Like normal

-- Can also have hidden types defined for derived types
type Object is abstract tagged private;

Interfaces#

Interfaces are a more restricted version of abstract types. Similarly to abstract types, objects cannot be created directly from an interface, but interfaces may also not have any concrete operations except for null or class-wide procedures.

type T is interface;
procedure Op_1(X: T) is abstract; -- Must be defined by the children
procedure Op_2(X: T) is null;     -- Can define null procedures
procedure Op_3(X: T'Class);       -- Can define class-wide subprograms

Controlled Types#

Package

Controlled types give access to three different activities for objects:

  1. Initialisation after creation (Initialize)
  2. Finalisation before destruction (Finalize)
  3. Adjustment after assignment (Adjust)

In order for a type to be controlled, it must be derived from either Ada.Finalization.Controlled or Ada.Finalization.Limited_Controlled and then the subprograms may be overloaded as needed.

with Ada.Finalization; use Ada.Finalization;

declare
   type T is new Controlled with record null; end record;

   X: T;
   -- Initialize(X);
begin
   -- Finalize(X);
   X := Y;
   -- Adjust(X);
   -- Finalize(X);
end;
A finalize procedure must not raise an exception. It is possible in some obscure circumstances that the finalize procedure is called twice. To avoid any possible issues, you should write it so as to not be affected by a second call.

Multiple Inheritance#

Multiple inheritance is allowed, but on the condition that only one parent has components and concrete operations. Interfaces are the natural match as they do not have any components and the have no non-null concrete operations. A summary of this would be to say that a tagged type may be derived from zero or one conventional tagged types plus zero or more interface types.

type MT is new T and TT with -- ...

-- Interface inheritance
type IT1 is interface;
type IT2 is interface and IT1;
The conventional tagged type is the parent and the interfaces are called progenitors.

Parametrised Types#

Parametrised types are those with something called discriminants. Discriminants can be either discrete or access types and all composite types except arrays (there are unconstrained arrays for that) may have them. Once the variable has been declared, it may not be changed and the discriminant fields are automatically added to the type. This is known as a constrained type.

declare
   type My_Array is array(Positive range <>) of Integer;
   type My_Record(Length: Positive) is record
      Data: My_Array(1 .. Length);
   end record;

   X: My_Record(3);
   Y: My_Record(Length => 6);
   Z: My_Record := (9, Data => (others => 7));
begin
   X.Data := (others => 77);
   -- Length is like a constant field
   Put_Line(Integer'Image(X.Length)); -- 3
end;

Default Values#

Default values in discriminants allows for an unconstrained type. This means that the discriminant values may be changed after declaration (but must be done as a whole – not just the discriminant).

declare
   subtype My_Length is Positive range 1 .. 100;
   type My_Array is array(My_Length range <>) of Integer;
   type My_Record(Length: My_Length := 1) is record
      Data: My_Array(1 .. Length);
   end record;

   X: My_Record(3);                    -- Same constrained type as the previous example
   Y: My_Record := (3, (others => 0)); -- Now an unconstrained type
   Z: access My_Record;
begin
   Y := (5, (others => 77));
   -- The size of Y was allowed to change
   Put_Line(Integer'Image(Y.Length)); -- 5

   Put_Line(Integer'Image(X'Size)); -- 128
   Put_Line(Integer'Image(Y'Size)); -- 3232

   Z := new My_Record'(10, (others => 0));
   Put_Line(Integer'Image(Z.all'Size)); -- 352
end;

Memory Usage

Note that in this case a simple range of Positive cannot be used as the size of the My_Record object is taken from the maximum. Because X is constrained, it has an expected size of 128 bits, but Y’s size is 3232 bits (\(\frac{3232}{8*4} = 101\))! So, the method which is used to “resize” the unconstrained value without heap allocation is to allocate the whole object and only use part of the memory. Of course, this makes sense otherwise there would be restrictions on unconstrained discriminants such as not being allowed in arrays. The example of Z does not have the padding because it is not allocated in the stack (\(\frac{352}{8*4} = 11\)).

Because the same type can be either constrained or unconstrained, there are two boolean attributes for checking: Constrained and Unconstrained.

Variants#

Variants are an alternative to tagged types which use a discriminant to allow for multiple implementations of a record. Variant types lead to subtypes of the same type, whereas tagged types are each distinct types. The discriminant cannot be changed after its declaration, but giving a default discriminant value allows for an unconstrained type in the same way as before. Although each alternative may contain any number of fields (or null for none), there may not be repeated identifiers.

declare
   type Gender is (Male, Female);
   type Person(Sex: Gender) is record
      Birth: Integer;
      case Sex is
      when Male   => Bearded : Boolean;
      when Female => Children: Integer;
      end case;
   end record;

   X: Person(Female);
begin
   Put_Line(Integer'Image(X'Size)); -- 96
end;
The type becomes unconstrained when using default values for the discriminant which means the variant type is effectively a tagged union (of the C kind).

When deciding on tagged vs variant types, the main difference is mutability: unconstrained variants may be changed to a “different” type whereas the tag for a tagged type cannot be changed.

Discriminants with Derived Types#

Deriving from a type will inherit the discriminant fields if the derived type does not declare its own. So, derived types with discriminants will either (1) inherit the discriminants if the child type does not have any of its own or (2) constrain (define) the parent’s discriminants and not inherit the discriminant fields.

Examples of deriving from a non-tagged type with discriminants:

type My_Type(D1, D2: Integer) is record -- ...

type My_Type_V2(D1, D2: Integer) is new My_Type(D1 => D1, D2 => D2);
type My_Type_V3(D     : Integer) is new My_Type(D1 => D , D2 => 2);
type My_Type_V4(D: Integer) is new My_Type(D, D);
type My_Type_V5 is new My_Type;
Here, My_Type_V2 has the D1 and D2 discriminants that it defined itself, My_Type_V3 and My_Type_V4 both have only their D discriminant and My_Type_V5 has the D1 and D2 discriminants inherited from My_Type.

Deriving from tagged type with discriminants is very similar to non-tagged types:

type My_Type(D1: Integer) is tagged record -- ...
type My_Type_V2 is new My_Type with -- ...
type My_Type_V3(D2: Integer) is new My_Type(1) with -- ...
Here, My_Type_V2 has the D1 discriminant field, but My_Type_V3 does not because the D2 discriminant overrides it and requires that the parent be constrained with the definition of D1.

Access Types with Discriminants#

Access types can refer to types with discriminants that have not been specified.

type My_Type(D: Integer) is record -- ...
type My_Type_Access is access all My_Type;

Private Types with Discriminants#

Private types that have discriminants may either:

  1. Hide the discriminants (and likely use a default value for the discriminant)
  2. Expose the discriminants
  3. Declare it with unknown discriminants (which it does not have to have)

type Private_Type_1 is private;
type Private_Type_2(D: Integer) is private;
type Private_Type_3(<>) is private;
Declare a type with unknown discriminants makes it indefinite and prevents the user from declaring initialised objects. The user then cannot create objects of the type unless the package provides a way to such as through a function. This is similar to a class-wide type that has the unknown discriminant of its tag.

Access Discriminants#

Self-referential Structure Discriminants that are access types allow for parametrising an object with some other object. An interesting construct is possible where an object is made aware of and ties to the object it is inside of. This is called a self-referential structure.

type Inner(Acc: access Outer) is limited -- ...
type Outer is limited record
   Child: Inner(Outer'Access);
end record;
When the discriminant is given a default value, it must be marked as limited in order to prevent any chance of reassignment. The two objects are permanently joined together.

Generics#

Generics allow static polymorphism for packages and subprograms. Generic parameters can be types, subprograms and packages as well values and are applied with instantiations that specify the parameters of the generic.

Generic Subprogram
generic type Item is private;
procedure Swap(A, B: in out Item);
-- ...
procedure Swap(A, B: in out Item) is
   Temp: Item := B;
begin
   B := A;
   A := Temp;
end;
-- ...
procedure Swap is new Swap(Integer);
See the examples for a full generic package example. A generic package cannot be use‘ed, but a specific instantiation must be made of the package (which can be useed, if needed).
Generic Package
generic
   type T is private;
   X: Integer;
   Y: Float := 1.0;
package Generic_Package is
-- ...

package Generic_Instantiation is new Generic_Package(Integer, 2);
use Generic_Instantiation;
Generic value parameters may also be in out in which case the value provided must be a variable. In addition, not null, constant, subprogram accesses, etc. may all be used in generic parameters.
generic G: in out not null access Some_Type;
generic P: access function(X, Y: Float) return Float;
Keep in mind that generic packages are not packages and generic subprograms are not subprograms. Once you instantiate a generic, it is then its counterpart.

Type Parameters#

Type parameters are typical and the private keyword being used to indicate that the implementation of the type is currently unknown. The parameters can refer to previously declared parameters in the generic definition.

Examples of Generic Type Parameters
generic
   type T1 is private;                    -- Any type
   type T2 is limited private;            -- And/Or tagged and abstract
   type T3(D1, D2: Integer) is private;   -- A type with two Integer discriminants
   type T4(<>) is private;                -- A type with unknown discriminants
   type T5;                               -- An Incomplete type
   type T6(D: Integer) is tagged private; -- An Incomplete tagged type with a discriminant
   type T7 is new S1;                     -- T7 must be derived from S1
   type T8 is new S2 with private;        -- As before, but for a tagged S2
   type T9 is interface and X;            -- Any interface descended from X
   type T10 is (<>);                      -- Any discrete type
   type T11 is digits <>;                 -- Any floating-point type (digits can also be mod, range, etc.)
-- ...

Default Type Parameters

In Ada2022, generic type parameters may have default types via or use:

generic
   type T is (<>) or use My_Enum;

Subprogram Parameters#

Parameters may also be added that add requirements for certain subprograms to be made available.

generic
   type Index is (<>);
   type Item is private;
   type Sequence is array(Index range <>) of Item;
   with function "<"(A, B: Item) return Boolean;
procedure Sort(Seq: in out Sequence);
-- ...
procedure Sort_Vector is new Sort(Integer, Float, Vector, "<");
This allows the ”<” function to be required without having to limit the types Item can be (for example, by using <> or digits <>). The implementation will use the function provided in the instantiation of the generic which allows for:
procedure Sort_Vector_Reverse is new Sort(Integer, Float, Vector, ">");
Despite the Sort implementation using < (ie, < is made to mean > for Sort_Vector_Reverse).

A default value may be given in various ways for generic subprogram parameters.

  1. with function "<"(A, B: Item) return Boolean is <>;
    Use whatever equivalent is available at the instantiation. In the case above with Item being Float, the intrinsic ”<” for floats will be used. The subprogram must have the same name and definition as the generic requires.
  2. with function "<"(A, B: Item) return Boolean is Less_Than;
    Use the specific subprogram specified (Less_Than here which must, of course, have a matching definition). It is also possible that this is an attribute of the type such as T'Pred or T'Succ.
  3. with procedure P(...) is null;
    Specifically for procedures, a null procedure may set as the default.

Package Parameters#

Generic packages may be parametrised with instantiations of other generic packages.

generic
   with package P is new Q(<>);
   with package Q is new Q(P1, P2 => <>, P3 => <>);
   with package R is new Q(P1, others => <>);
   use P; -- legal in generic parameters
One possible use is to group common generic parameters that are use across different packages into a single generic package that can be used as a parameter to the aforementioned packages.
generic
   type Index is (<>);
   type Item  is private;
   type Vec   is array(Index range <>) of Item;
package General_Package is end;
-- ...
generic
   with package P is new General_Package(<>);
Examples of generic packages can be seen in many container packages, such as the vectors package or the sets package.