Access Types
We discussed access types back in the Introduction to Ada course. In this chapter, we discuss further details about access types and techniques when using them. Before we dig into details, however, we're going to make sure we understand the terminology.
Access types: Terminology
In this section, we discuss some of the terminology associated with access types. Usually, the terms used in Ada when discussing references and dynamic memory allocation are different than the ones you might encounter in other languages, so it's necessary you understand what each term means.
Access type, designated subtype and profile
The first term we encounter is (obviously) access type, which is a type that
provides us access to an object or a subprogram. We declare access types by
using the access
keyword:
package Show_Access_Type_Declaration is -- -- Declaring access types: -- -- Access-to-object type type Integer_Access is access Integer; -- Access-to-subprogram type type Init_Integer_Access is access function return Integer; end Show_Access_Type_Declaration;
Here, we're declaring two access types: the access-to-object type
Integer_Access
and the access-to-subprogram type
Init_Integer_Access
. (We discuss access-to-subprogram types
later on).
In the declaration of an access type, we always specify — after the
access
keyword — the kind of thing we want to designate. In the
case of an access-to-object type declaration, we declare a subtype we want to
access, which is known as the designated subtype of an access type. In the
case of an access-to-subprogram type declaration, the subprogram prototype is
known as the designated profile.
In our previous code example, Integer
is the designated subtype of the
Integer_Access
type, and function return Integer
is the
designated profile of the Init_Integer_Access
type.
Important
In contrast to other programming languages, an access type is not a pointer, and it doesn't just indicate an address in memory. We discuss more about addresses later on.
Access object and designated object
We use an access-to-object type by first declaring a variable (or constant) of
an access type and then allocating an object. (This is actually just one way of
using access types; we discuss other methods later in this chapter.) The actual
variable or constant of an access type is called access object, while the
object we allocate (via new
) is the designated object.
For example:
procedure Show_Simple_Allocation is -- Access-to-object type type Integer_Access is access Integer; -- Access object I1 : Integer_Access; begin I1 := new Integer; -- ^^^^^^^^^^^ allocating an object, -- which becomes the designated -- object for I1 end Show_Simple_Allocation;
In this example, I1
is an access object and the object allocated via
new Integer
is its designated object.
Access value and designated value
An access object and a designated (allocated) object, both store values. The value of an access object is the access value and the value of a designated object is the designated value. For example:
procedure Show_Values is -- Access-to-object type type Integer_Access is access Integer; I1, I2, I3 : Integer_Access; begin I1 := new Integer; I3 := new Integer; -- Copying the access value of I1 to I2 I2 := I1; -- Copying the designated value of I1 I3.all := I1.all; end Show_Values;
In this example, the assignment I2 := I1
copies the access value of
I1
to I2
. The assignment I3.all := I1.all
copies
I1
's designated value to I3
's designated object.
(As we already know, .all
is used to dereference an access object. We
discuss this topic again later in this chapter.)
In the Ada Reference Manual
Access types: Allocation
Ada makes the distinction between pool-specific and general access types, as we'll discuss in this section. Before doing so, however, let's talk about memory allocation.
In general terms, memory can be allocated dynamically on the heap or statically on the stack. (Strictly speaking, both are dynamic allocations, in that they occur at run-time with amounts not previously specified.) For example:
procedure Show_Simple_Allocation is -- Declaring access type: type Integer_Access is access Integer; -- Declaring access object: A1 : Integer_Access; begin -- Allocating an Integer object on the heap A1 := new Integer; declare -- Allocating an Integer object on the -- stack I : Integer; begin null; end; end Show_Simple_Allocation;
When we allocate an object on the heap via new
, the allocation happens
in a memory pool that is associated with the access type. In our code example,
there's a memory pool associated with the Integer_Access
type, and each
new Integer
allocates a new integer object in that pool. Therefore,
access types of this kind are called pool-specific access types. (We discuss
more about these types later.)
It is also possible to access objects that were allocated on the stack. To do that, however, we cannot use pool-specific access types because — as the name suggests — they're only allowed to access objects that were allocated in the specific pool associated with the type. Instead, we have to use general access types in this case:
procedure Show_General_Access_Type is -- Declaring general access type: type Integer_Access is access all Integer; -- Declaring access object: A1 : Integer_Access; -- Allocating an Integer object on the -- stack: I : aliased Integer; begin -- Getting access to an Integer object that -- was allocated on the stack A1 := I'Access; end Show_General_Access_Type;
In this example, we declare the general access type Integer_Access
and
the access object A1
. To initialize A1
, we write I'Access
to get access to an integer object I
that was allocated on the stack.
(For the moment, don't worry much about these details: we'll talk about general
access types again when we introduce the topic of
aliased objects later on.)
For further reading...
Note that it is possible to use general access types to allocate objects on the heap:
procedure Show_Simple_Allocation is -- Declaring general access type: type Integer_Access is access all Integer; -- Declaring access object: A1 : Integer_Access; begin -- -- Allocating an Integer object on the heap -- and initializing an access object of -- the general access type Integer_Access. -- A1 := new Integer; end Show_Simple_Allocation;
Here, we're using a general access type Integer_Access
, but
allocating an integer object on the heap.
Important
In many code examples, we have used the Integer
type as the
designated subtype of the access types — by writing
access Integer
. Although we have used this specific scalar type,
we aren't really limited to those types. In fact, we can use any type as
the designated subtype, including user-defined types, composite types,
task types and protected types.
In the Ada Reference Manual
Pool-specific access types
We've already discussed many aspects about pool-specific access types. In this section, we recapitulate some of those aspects, and discuss some new details that haven't seen yet.
As we know, we cannot directly assign an object Distance_Miles
of type
Miles
to an object Distance_Meters
of type Meters
, even if
both share a common Float
type ancestor. The assignment is only possible
if we perform a type conversion from Miles
to Meters
, or
vice-versa — e.g.:
Distance_Meters := Meters (Distance_Miles) * Miles_To_Meters_Factor
.
Similarly, in the case of pool-specific access types, a direct assignment
between objects of different access types isn't possible. However, even if
both access types have the same designated subtype (let's say, they are both
declared using is access Integer
), it's still not possible to perform
a type conversion between those access types. The only situation when an access
type conversion is allowed is when both types have a common ancestor.
Let's see an example:
pragma Ada_2022; with Ada.Text_IO; use Ada.Text_IO; procedure Show_Simple_Allocation is -- Declaring pool-specific access type: type Integer_Access_1 is access Integer; type Integer_Access_2 is access Integer; type Integer_Access_2B is new Integer_Access_2; -- Declaring access object: A1 : Integer_Access_1; A2 : Integer_Access_2; A2B : Integer_Access_2B; begin A1 := new Integer; Put_Line ("A1 : " & A1'Image); Put_Line ("Pool: " & A1'Storage_Pool'Image); A2 := new Integer; Put_Line ("A2: " & A2'Image); Put_Line ("Pool: " & A2'Storage_Pool'Image); -- ERROR: Cannot directly assign access values -- for objects of unrelated access -- types; also, cannot convert between -- these types. -- -- A1 := A2; -- A1 := Integer_Access_1 (A2); A2B := Integer_Access_2B (A2); Put_Line ("A2B: " & A2B'Image); Put_Line ("Pool: " & A2B'Storage_Pool'Image); end Show_Simple_Allocation;
In this example, we declare three access types: Integer_Access_1
,
Integer_Access_2
and Integer_Access_2B
. Also,
the Integer_Access_2B
type is derived from the Integer_Access_2
type. Therefore, we can convert an object of Integer_Access_2
type to
the Integer_Access_2B
type — we do this in the
A2B := Integer_Access_2B (A2)
assignment. However, we cannot directly
assign to or convert between unrelated types such as Integer_Access_1
and Integer_Access_2
. (We would get a compilation error if we included
the A1 := A2
or the A1 := Integer_Access_1 (A2)
assignment.)
Important
Remember that:
As mentioned in the Introduction to Ada course:
an access type can be unconstrained, but the actual object allocation must be constrained;
we can use a qualified expression to allocate an object.
We can use the
Storage_Size
attribute to limit the size of the memory pool associated with an access type, as discussed previously in the section about storage size.When running out of memory while allocating via
new
, we get aStorage_Error
exception because of the storage check.
For example:
pragma Ada_2022; with Ada.Text_IO; use Ada.Text_IO; procedure Show_Array_Allocation is -- Unconstrained array type: type Integer_Array is array (Positive range <>) of Integer; -- Access type with unconstrained -- designated subtype and limited storage -- size. type Integer_Array_Access is access Integer_Array with Storage_Size => 128; -- An access object: A1 : Integer_Array_Access; procedure Show_Info (IAA : Integer_Array_Access) is begin Put_Line ("Allocated: " & IAA'Image); Put_Line ("Length: " & IAA.all'Length'Image); Put_Line ("Values: " & IAA.all'Image); end Show_Info; begin -- Allocating an integer array with -- constrained range on the heap: A1 := new Integer_Array (1 .. 3); A1.all := [others => 42]; Show_Info (A1); -- Allocating an integer array on the -- heap using a qualified expression: A1 := new Integer_Array'(5, 10); Show_Info (A1); -- A third allocation fails at run time -- because of the constrained storage -- size: A1 := new Integer_Array (1 .. 100); Show_Info (A1); exception when Storage_Error => Put_Line ("Out of memory!"); end Show_Array_Allocation;
Multiple allocation
Up to now, we have seen examples of allocating a single object on the heap. It's possible to allocate multiple objects at once as well — i.e. syntactic sugar is available to simplify the code that performs this allocation. For example:
pragma Ada_2022; with Ada.Text_IO; use Ada.Text_IO; procedure Show_Access_Array_Allocation is type Integer_Access is access Integer; type Integer_Access_Array is array (Positive range <>) of Integer_Access; -- An array of access objects: Arr : Integer_Access_Array (1 .. 10); begin -- -- Allocating 10 access objects and -- initializing the corresponding designated -- object with zero: -- Arr := (others => new Integer'(0)); -- Same as: for I in Arr'Range loop Arr (I) := new Integer'(0); end loop; Put_Line ("Arr: " & Arr'Image); Put_Line ("Arr (designated values): "); for E of Arr loop Put (E.all'Image); end loop; end Show_Access_Array_Allocation;
In this example, we have the access type Integer_Access
and an array
type of this access type (Integer_Access_Array
). We also declare an
array Arr
of Integer_Access_Array
type. This means that each
component of Arr
is an access object. We allocate all ten components of
the Arr
array by simply writing Arr := (others => new Integer)
.
This array aggregate is syntactic sugar for a
loop over Arr
that allocates each component. (Note that, by writing
Arr := (others => new Integer'(0))
, we're also initializing the
designated objects with zero.)
Let's see another code example, this time with task types:
package Workers is task type Worker is entry Start (Id : Positive); entry Stop; end Worker; type Worker_Access is access Worker; type Worker_Array is array (Positive range <>) of Worker_Access; end Workers;with Ada.Text_IO; use Ada.Text_IO; package body Workers is task body Worker is Id : Positive; begin accept Start (Id : Positive) do Worker.Id := Id; end Start; Put_Line ("Started Worker #" & Id'Image); accept Stop; Put_Line ("Stopped Worker #" & Id'Image); end Worker; end Workers;with Ada.Text_IO; use Ada.Text_IO; with Workers; use Workers; procedure Show_Workers is Worker_Arr : Worker_Array (1 .. 20); begin -- -- Allocating 20 workers at once: -- Worker_Arr := (others => new Worker); for I in Worker_Arr'Range loop Worker_Arr (I).Start (I); end loop; Put_Line ("Some processing..."); delay 1.0; for W of Worker_Arr loop W.Stop; end loop; end Show_Workers;
In this example, we declare the task type Worker
, the access type
Worker_Access
and an array of access to tasks Worker_Array
.
Using this approach, a task is only created when we allocate an individual
component of an array of Worker_Array
type. Thus, when we declare
the Worker_Arr
array in this example, we're only preparing a container
of 20 workers, but we don't have any actual tasks yet. We bring the 20 tasks
into existence by writing Worker_Arr := (others => new Worker)
.
Discriminants as Access Values
We can use access types when declaring discriminants. Let's see an example:
package Custom_Recs is -- Declaring an access type: type Integer_Access is access Integer; -- Declaring a discriminant with this -- access type: type Rec (IA : Integer_Access) is record I : Integer := IA.all; -- ^^^^^^^^^ -- Setting I's default to use the -- designated value of IA: end record; procedure Show (R : Rec); end Custom_Recs;with Ada.Text_IO; use Ada.Text_IO; package body Custom_Recs is procedure Show (R : Rec) is begin Put_Line ("R.IA = " & Integer'Image (R.IA.all)); Put_Line ("R.I = " & Integer'Image (R.I)); end Show; end Custom_Recs;with Custom_Recs; use Custom_Recs; procedure Show_Discriminants_As_Access_Values is IA : constant Integer_Access := new Integer'(10); R : Rec (IA); begin Show (R); IA.all := 20; R.I := 30; Show (R); -- As expected, we cannot change the -- discriminant. The following line is -- triggers a compilation error: -- -- R.IA := new Integer; end Show_Discriminants_As_Access_Values;
In the Custom_Recs
package from this example, we declare the access
type Integer_Access
. We then use this type to declare the discriminant
(IA
) of the Rec
type. In the
Show_Discriminants_As_Access_Values
procedure, we see that (as expected)
we cannot change the discriminant of an object of Rec
type: an
assignment such as R.IA := new Integer
would trigger a compilation
error.
Note that we can use a default for the discriminant:
package Custom_Recs is type Integer_Access is access Integer; type Rec (IA : Integer_Access := new Integer'(0)) is -- ^^^^^^^^^^^^^^^ -- default value record I : Integer := IA.all; end record; procedure Show (R : Rec); end Custom_Recs;with Custom_Recs; use Custom_Recs; procedure Show_Discriminants_As_Access_Values is R1 : Rec; -- ^^^ -- no discriminant: use default R2 : Rec (new Integer'(20)); -- ^^^^^^^^^^^^^^^^ -- allocating an unnamed integer object begin Show (R1); Show (R2); end Show_Discriminants_As_Access_Values;
Here, we've changed the declaration of the Rec
type to allocate an
integer object if the type's discriminant isn't provided — we can see
this in the declaration of the R1
object in the
Show_Discriminants_As_Access_Values
procedure. Also, in this
procedure, we're allocating an unnamed integer object in the declaration
of R2
.
In the Ada Reference Manual
Unconstrained type as designated subtype
Notice that we were using a scalar type as the designated subtype of the
Integer_Access
type. We could have used an unconstrained type as well.
In fact, this is often used for the sake of having the effect of an
unconstrained discriminant type.
Let's see an example:
package Persons is -- Declaring an access type whose -- designated subtype is unconstrained: type String_Access is access String; -- Declaring a discriminant with this -- access type: type Person (Name : String_Access) is record Age : Integer; end record; procedure Show (P : Person); end Persons;with Ada.Text_IO; use Ada.Text_IO; package body Persons is procedure Show (P : Person) is begin Put_Line ("Name = " & P.Name.all); Put_Line ("Age = " & Integer'Image (P.Age)); end Show; end Persons;with Persons; use Persons; procedure Show_Person is P : Person (new String'("John")); begin P.Age := 30; Show (P); end Show_Person;
In this example, the discriminant of the Person
type has an
unconstrained designated type. In the Show_Person
procedure, we declare
the P
object and specify the constraints of the allocated string object
— in this case, a four-character string initialized with the name "John".
For further reading...
In the previous code example, we used an array — actually, a string — to demonstrate the advantage of using discriminants as access values, for we can use an unconstrained type as the designated subtype. In fact, as we discussed earlier in another chapter, we can only use discrete types (or access types) as discriminants. Therefore, you wouldn't be able to use a string, for example, directly as a discriminant without using access types:
package Persons is -- ERROR: Declaring a discriminant with an -- unconstrained type: type Person (Name : String) is record Age : Integer; end record; end Persons;
As expected, compilation fails for this code because the discriminant of
the Person
type is indefinite.
However, the advantage of discriminants as access values isn't restricted to being able to use unconstrained types such as arrays: we could really use any type as the designated subtype! In fact, we can generalized this to:
generic type T (<>); -- any type type T_Access is access T; package Gen_Custom_Recs is -- Declare a type whose discriminant D can -- access any type: type T_Rec (D : T_Access) is null record; end Gen_Custom_Recs;with Gen_Custom_Recs; package Custom_Recs is type Incomp; -- Incomplete type declaration! type Incomp_Access is access Incomp; -- Instantiating package using -- incomplete type Incomp: package Inst is new Gen_Custom_Recs (T => Incomp, T_Access => Incomp_Access); subtype Rec is Inst.T_Rec; -- At this point, Rec (Inst.T_Rec) uses -- an incomplete type as the designated -- subtype of its discriminant type procedure Show (R : Rec) is null; -- Now, we complete the Incomp type: type Incomp (B : Boolean := True) is private; private -- Finally, we have the full view of the -- Incomp type: type Incomp (B : Boolean := True) is null record; end Custom_Recs;with Custom_Recs; use Custom_Recs; procedure Show_Rec is R : Rec (new Incomp); begin Show (R); end Show_Rec;
In the Gen_Custom_Recs
package, we're using type T (<>)
— which can be any type — for the designated subtype of the
access type T_Access
, which is the type of T_Rec
's
discriminant. In the Custom_Recs
package, we use the incomplete type
Incomp
to instantiate the generic package. Only after the
instantiation, we declare the complete type.
Later on, we'll discuss discriminants again when we look into anonymous access discriminants, which provide some advantages in terms of accessibility rules.
Whole object assignments
As expected, we cannot change the discriminant value in whole object
assignments. If we do that, the Constraint_Error
exception is raised
at runtime:
with Persons; use Persons; procedure Show_Person is S1 : String_Access := new String'("John"); S2 : String_Access := new String'("Mark"); P : Person := (Name => S1, Age => 30); begin P := (Name => S1, Age => 31); -- ^^ OK: we didn't change the -- discriminant. Show (P); -- We can just repeat the discriminant: P := (Name => P.Name, Age => 32); -- ^^^^^^ OK: we didn't change the -- discriminant. Show (P); -- Of course, we can change the string itself: S1.all := "Mark"; Show (P); P := (Name => S2, Age => 40); -- ^^ ERROR: we changed the -- discriminant! Show (P); end Show_Person;
The first and the second assignments to P
are OK because we didn't
change the discriminant. However, the last assignment raises the
Constraint_Error
exception at runtime because we're changing the
discriminant.
Parameters as Access Values
In addition to
using discriminants as access values,
we can use access types for subprogram formal parameters. For example, the
N
parameter of the Show
procedure below has an access type:
package Names is type Name is access String; procedure Show (N : Name); end Names;
This is the complete code example:
package Names is type Name is access String; procedure Show (N : Name); end Names;with Ada.Text_IO; use Ada.Text_IO; package body Names is procedure Show (N : Name) is begin Put_Line ("Name: " & N.all); end Show; end Names;with Names; use Names; procedure Show_Names is N : Name := new String'("John"); begin Show (N); end Show_Names;
Note that in this example, the Show
procedure is basically just
displaying the string. Since the procedure isn't doing anything that justifies
the need for an access type, we could have implemented it with a simpler
type:
package Names is type Name is access String; procedure Show (N : String); end Names;with Ada.Text_IO; use Ada.Text_IO; package body Names is procedure Show (N : String) is begin Put_Line ("Name: " & N); end Show; end Names;with Names; use Names; procedure Show_Names is N : Name := new String'("John"); begin Show (N.all); end Show_Names;
It's important to highlight the difference between passing an access value to
a subprogram and passing an object by reference. In both versions of this code
example, the compiler will make use of a reference for the actual parameter of
the N
parameter of the Show
procedure. However, the difference
between these two cases is that:
N : Name
is a reference to an object (because it's an access value) that is passed by value, andN : String
is an object passed by reference.
Changing the referenced object
Since the Name
type gives us access to an object in the Show
procedure, we could actually change this object inside the procedure. To
illustrate this, let's change the Show
procedure to lower each
character of the string before displaying it (and rename the procedure to
Lower_And_Show
):
package Names is type Name is access String; procedure Lower_And_Show (N : Name); end Names;with Ada.Text_IO; use Ada.Text_IO; with Ada.Characters.Handling; use Ada.Characters.Handling; package body Names is procedure Lower_And_Show (N : Name) is begin for I in N'Range loop N (I) := To_Lower (N (I)); end loop; Put_Line ("Name: " & N.all); end Lower_And_Show; end Names;with Names; use Names; procedure Show_Changed_Names is N : Name := new String'("John"); begin Lower_And_Show (N); end Show_Changed_Names;
Notice that, again, we could have implemented the Lower_And_Show
procedure without using an access type:
package Names is type Name is access String; procedure Lower_And_Show (N : in out String); end Names;with Ada.Text_IO; use Ada.Text_IO; with Ada.Characters.Handling; use Ada.Characters.Handling; package body Names is procedure Lower_And_Show (N : in out String) is begin for I in N'Range loop N (I) := To_Lower (N (I)); end loop; Put_Line ("Name: " & N); end Lower_And_Show; end Names;with Names; use Names; procedure Show_Changed_Names is N : Name := new String'("John"); begin Lower_And_Show (N.all); end Show_Changed_Names;
Replace the access value
Instead of changing the object in the Lower_And_Show
procedure, we
could replace the access value by another one — for example, by
allocating a new string inside the procedure. In this case, we have to pass the
access value by reference using the in out
parameter mode:
package Names is type Name is access String; procedure Lower_And_Show (N : in out Name); end Names;with Ada.Text_IO; use Ada.Text_IO; with Ada.Characters.Handling; use Ada.Characters.Handling; package body Names is procedure Lower_And_Show (N : in out Name) is begin N := new String'(To_Lower (N.all)); Put_Line ("Name: " & N.all); end Lower_And_Show; end Names;with Names; use Names; procedure Show_Changed_Names is N : Name := new String'("John"); begin Lower_And_Show (N); end Show_Changed_Names;
Now, instead of changing the object referenced by N
, we're actually
replacing it with a new object that we allocate inside the
Lower_And_Show
procedure.
As expected, contrary to the previous examples, we cannot implement this code by relying on parameter modes to replace the object. In fact, we have to use access types for this kind of operations.
Note that this implementation creates a memory leak. In a proper implementation, we should make sure to deallocate the object, as explained later on.
Side-effects on designated objects
In previous code examples from this section, we've seen that passing a
parameter by reference using the in
or in out
parameter modes
is an alternative to using access values as parameters. Let's focus on the
subprogram declarations of those code examples and their parameter modes:
Subprogram |
Parameter type |
Parameter mode |
---|---|---|
|
|
|
|
|
|
|
|
|
|
|
|
When we analyze the information from this table, we see that in the case of
using strings with different parameter modes, we have a clear indication
whether the subprogram might change the object or not. For example,
we know that a call to Show (N : String)
won't change the string object
that we're passing as the actual parameter.
In the case of passing an access value, we cannot know whether the
designated object is going to be altered by a call to the subprogram. In fact,
in both Show
and Lower_And_Show
procedures, the parameter is the
same: N : Name
— in other words, the parameter mode is in
in both cases. Here, there's no clear indication about the effects of a
subprogram call on the designated object.
The simplest way to ensure that the object isn't changed in the subprogram is
by using
access-to-constant types, which we
discuss later on. In this case, we're basically saying that the object we're
accessing in Show
is constant, so we cannot possibly change it:
package Names is type Name is access String; type Constant_Name is access constant String; procedure Show (N : Constant_Name); end Names;with Ada.Text_IO; use Ada.Text_IO; -- with Ada.Characters.Handling; -- use Ada.Characters.Handling; package body Names is procedure Show (N : Constant_Name) is begin -- for I in N'Range loop -- N (I) := To_Lower (N (I)); -- end loop; Put_Line ("Name: " & N.all); end Show; end Names;with Names; use Names; procedure Show_Names is N : Name := new String'("John"); begin Show (Constant_Name (N)); end Show_Names;
In this case, the Constant_Name
type ensures that the N
parameter won't be changed in the Show
procedure. Note that we need
to convert from Name
to Constant_Name
to be able to call the
Show
procedure (in the Show_Names
procedure). Although using
in String
is still a simpler solution, this approach works fine.
(Feel free to uncomment the call to To_Lower
in the Show
procedure and the corresponding with- and use-clauses to see that the
compilation fails when trying to change the constant object.)
We could also mitigate the problem by using contracts. For example:
package Names is type Name is access String; procedure Show (N : Name) with Post => N.all'Old = N.all; -- ^^^^^^^^^^^^^^^^^ -- we promise that we won't change -- the object end Names;with Ada.Text_IO; use Ada.Text_IO; -- with Ada.Characters.Handling; -- use Ada.Characters.Handling; package body Names is procedure Show (N : Name) is begin -- for I in N'Range loop -- N (I) := To_Lower (N (I)); -- end loop; Put_Line ("Name: " & N.all); end Show; end Names;with Names; use Names; procedure Show_Names is N : Name := new String'("John"); begin Show (N); end Show_Names;
Although a bit more verbose than a simple in String
, the information in
the specification of Show
at least gives us an indication that the
object won't be affected by the call to this subprogram. Note that this code
actually compiles if we try to modify N.all
in the Show
procedure, but the post-condition fails at runtime when we do that.
(By uncommentating and building the code again, you'll see an exception being raised at runtime when trying to change the object.)
In the postcondition above, we're using 'Old
to refer to the original
object before the subprogram call. Unfortunately, we cannot use this attribute
when dealing with
limited private types — or limited
types in general. For example, let's change the declaration of Name
and
have it as a limited private type instead:
package Names is type Name is limited private; function Init (S : String) return Name; function Equal (N1, N2 : Name) return Boolean; procedure Show (N : Name) with Post => Equal (N'Old = N); private type Name is access String; function Init (S : String) return Name is (new String'(S)); function Equal (N1, N2 : Name) return Boolean is (N1.all = N2.all); end Names;with Ada.Text_IO; use Ada.Text_IO; -- with Ada.Characters.Handling; -- use Ada.Characters.Handling; package body Names is procedure Show (N : Name) is begin -- for I in N'Range loop -- N (I) := To_Lower (N (I)); -- end loop; Put_Line ("Name: " & N.all); end Show; end Names;with Names; use Names; procedure Show_Names is N : Name := Init ("John"); begin Show (N); end Show_Names;
In this case, we have no means to indicate that a call to Show
won't
change the internal state of the actual parameter.
For further reading...
As an alternative, we could declare a new Constant_Name
type that
is also limited private. If we use this type in Show
procedure,
we're at least indicating (in the type name) that the type is supposed to
be constant — even though we're not directly providing means to
actually ensure that no modifications occur in a call to the procedure.
However, the fact that we declare this type as an access-to-constant (in
the private part of the specification) makes it clear that a call to
Show
won't change the designated object.
Let's look at the adapted code:
package Names is type Name is limited private; type Constant_Name is limited private; function Init (S : String) return Name; function To_Constant_Name (N : Name) return Constant_Name; procedure Show (N : Constant_Name); private type Name is access String; type Constant_Name is access constant String; function Init (S : String) return Name is (new String'(S)); function To_Constant_Name (N : Name) return Constant_Name is (Constant_Name (N)); end Names;with Ada.Text_IO; use Ada.Text_IO; -- with Ada.Characters.Handling; -- use Ada.Characters.Handling; package body Names is procedure Show (N : Constant_Name) is begin -- for I in N'Range loop -- N (I) := To_Lower (N (I)); -- end loop; Put_Line ("Name: " & N.all); end Show; end Names;with Names; use Names; procedure Show_Names is N : Name := Init ("John"); begin Show (To_Constant_Name (N)); end Show_Names;
In this version of the source code, the Show
procedure doesn't have
any side-effects, as we cannot modify N
inside the procedure.
Having the information about the effects of a subprogram call to an object is very important: we can use this information to set expectations — and avoid unexpected changes to an object. Also, this information can be used to prove that a program works as expected. Therefore, whenever possible, we should avoid access values as parameters. Instead, we can rely on appropriate parameter modes and pass an object by reference.
There are cases, however, where the design of our application doesn't permit replacing the access type with simple parameter modes. Whenever we have an abstract data type encapsulated as a limited private type — such as in the last code example —, we might have no means to avoid access values as parameters. In this case, using the access type is of course justifiable. We'll see such a case in the next section.
Self-reference
As we've discussed in the section about
incomplete types <Adv_Ada_Incomplete_Types>
, we can use incomplete types
to create a recursive, self-referencing type. Let's revisit a code example from
that section:
package Linked_List_Example is type Integer_List; type Next is access Integer_List; type Integer_List is record I : Integer; N : Next; end record; end Linked_List_Example;
Here, we're using the incomplete type Integer_List
in the declaration of
the Next
type, which we then use in the complete declaration of the
Integer_List
type.
Self-references are useful, for example, to create unbounded containers — such as the linked lists mentioned in the example above. Let's extend this code example and partially implement a generic package for linked lists:
generic type T is private; package Linked_Lists is type List is limited private; procedure Append_Front (L : in out List; E : T); procedure Append_Rear (L : in out List; E : T); procedure Show (L : List); private -- Incomplete type declaration: type Component; -- Using incomplete type: type List is access Component; type Component is record Value : T; Next : List; -- ^^^^ -- Self-reference via access type end record; end Linked_Lists;pragma Ada_2022; with Ada.Text_IO; use Ada.Text_IO; package body Linked_Lists is procedure Append_Front (L : in out List; E : T) is New_First : constant List := new Component'(Value => E, Next => L); begin L := New_First; end Append_Front; procedure Append_Rear (L : in out List; E : T) is New_Last : constant List := new Component'(Value => E, Next => null); begin if L = null then L := New_Last; else declare Last : List := L; begin while Last.Next /= null loop Last := Last.Next; end loop; Last.Next := New_Last; end; end if; end Append_Rear; procedure Show (L : List) is Curr : List := L; begin if L = null then Put_Line ("[ ]"); else Put ("["); loop Put (Curr.Value'Image); Put (" "); exit when Curr.Next = null; Curr := Curr.Next; end loop; Put_Line ("]"); end if; end Show; end Linked_Lists;with Linked_Lists; procedure Test_Linked_List is package Integer_Lists is new Linked_Lists (T => Integer); use Integer_Lists; L : List; begin Append_Front (L, 3); Append_Rear (L, 4); Append_Rear (L, 5); Append_Front (L, 2); Append_Front (L, 1); Append_Rear (L, 6); Append_Rear (L, 7); Show (L); end Test_Linked_List;
In this example, we declare an incomplete type Component
in the private
part of the generic Linked_Lists
package. We use this incomplete type to
declare the access type List
, which is then used as a self-reference in
the Next
component of the Component
type.
Note that we're using the List
type
as a parameter for the
Append_Front
, Append_Rear
and Show
procedures.
In the Ada Reference Manual
Mutually dependent types using access types
In the section on mutually dependent types, we've seen a code example where each type depends on the other one. We could rewrite that code example using access types:
package Mutually_Dependent is type T2; type T2_Access is access T2; type T1 is record B : T2_Access; end record; type T1_Access is access T1; type T2 is record A : T1_Access; end record; end Mutually_Dependent;
In this example, T1
and T2
are mutually dependent types via the
access types T1_Access
and T2_Access
— we're using those
access types in the declaration of the B
and A
components.
Dereferencing
In the Introduction to Ada course, we
discussed the .all
syntax to dereference access values:
with Ada.Text_IO; use Ada.Text_IO; procedure Show_Dereferencing is -- Declaring access type: type Integer_Access is access Integer; -- Declaring access object: A1 : Integer_Access; begin A1 := new Integer; -- Dereferencing access value: A1.all := 22; Put_Line ("A1: " & Integer'Image (A1.all)); end Show_Dereferencing;
In this example, we declare A1
as an access object, which allows us to
access objects of Integer
type. We dereference A1
by writing
A1.all
.
Here's another example, this time with an array:
with Ada.Text_IO; use Ada.Text_IO; procedure Show_Dereferencing is type Integer_Array is array (Positive range <>) of Integer; type Integer_Array_Access is access Integer_Array; Arr : constant Integer_Array_Access := new Integer_Array (1 .. 6); begin Arr.all := (1, 2, 3, 5, 8, 13); for I in Arr'Range loop Put_Line ("Arr (: " & Integer'Image (I) & "): " & Integer'Image (Arr.all (I))); end loop; end Show_Dereferencing;
In this example, we dereference the access value by writing Arr.all
. We
then assign an array aggregate to it — this becomes
Arr.all := (..., ...);
. Similarly, in the loop, we write
Arr.all (I)
to access the I
component of the array.
In the Ada Reference Manual
Implicit Dereferencing
Implicit dereferencing allows us to omit the .all
suffix without getting
a compilation error. In this case, the compiler knows that the dereferenced
object is implied, not the access value.
Ada supports implicit dereferencing in these use cases:
when accessing components of a record or an array — including array slices.
when accessing subprograms that have at least one parameter (we discuss this topic later in this chapter);
when accessing some attributes — such as some array and task attributes.
Arrays
Let's start by looking into an example of implicit dereferencing of arrays. We
can take the previous code example and replace Arr.all (I)
by
Arr (I)
:
with Ada.Text_IO; use Ada.Text_IO; procedure Show_Dereferencing is type Integer_Array is array (Positive range <>) of Integer; type Integer_Array_Access is access Integer_Array; Arr : constant Integer_Array_Access := new Integer_Array (1 .. 6); begin Arr.all := (1, 2, 3, 5, 8, 13); Arr (1 .. 6) := (1, 2, 3, 5, 8, 13); for I in Arr'Range loop Put_Line ("Arr (: " & Integer'Image (I) & "): " & Integer'Image (Arr (I))); -- ^ .all is implicit. end loop; end Show_Dereferencing;
Both forms — Arr.all (I)
and Arr (I)
— are
equivalent. Note, however, that there's no implicit dereferencing when we want
to access the whole array. (Therefore, we cannot write
Arr := (1, 2, 3, 5, 8, 13);
.) However, as slices are implicitly
dereferenced, we can write Arr (1 .. 6) := (1, 2, 3, 5, 8, 13);
instead
of Arr.all (1 .. 6) := (1, 2, 3, 5, 8, 13);
. Alternatively, we can
assign to the array components individually and use implicit dereferencing for
each component:
Arr (1) := 1;
Arr (2) := 2;
Arr (3) := 3;
Arr (4) := 5;
Arr (5) := 8;
Arr (6) := 13;
Implicit dereferencing isn't available for the whole array because we have to distinguish between assigning to access objects and assigning to actual arrays. For example:
with Ada.Text_IO; use Ada.Text_IO; procedure Show_Array_Assignments is type Integer_Array is array (Positive range <>) of Integer; type Integer_Array_Access is access Integer_Array; procedure Show_Array (Name : String; Arr : Integer_Array_Access) is begin Put (Name); for E of Arr.all loop Put (Integer'Image (E)); end loop; New_Line; end Show_Array; Arr_1 : constant Integer_Array_Access := new Integer_Array (1 .. 6); Arr_2 : Integer_Array_Access := new Integer_Array (1 .. 6); begin Arr_1.all := (1, 2, 3, 5, 8, 13); Arr_2.all := (21, 34, 55, 89, 144, 233); -- Array assignment Arr_2.all := Arr_1.all; Show_Array ("Arr_2", Arr_2); -- Access value assignment Arr_2 := Arr_1; Arr_1.all := (377, 610, 987, 1597, 2584, 4181); Show_Array ("Arr_2", Arr_2); end Show_Array_Assignments;
Here, Arr_2.all := Arr_1.all
is an array assignment, while
Arr_2 := Arr_1
is an access value assignment. By forcing the usage of
the .all
suffix, the distinction is clear. Implicit dereferencing,
however, could be confusing here. (For example, the .all
suffix in
Arr_2 := Arr_1.all
is an oversight by the programmer when the intention
actually was to use access values on both sides.) Therefore, implicit
dereferencing is only supported in those cases where there's no risk of
ambiguities or oversights.
Records
Let's see an example of implicit dereferencing of a record:
with Ada.Text_IO; use Ada.Text_IO; procedure Show_Dereferencing is type Rec is record I : Integer; F : Float; end record; type Rec_Access is access Rec; R : constant Rec_Access := new Rec; begin R.all := (I => 1, F => 5.0); Put_Line ("R.I: " & Integer'Image (R.I)); Put_Line ("R.F: " & Float'Image (R.F)); end Show_Dereferencing;
Again, we can replace R.all.I
by R.I
, as record components are
implicitly dereferenced. Also, we could use implicit dereference when assigning
to record components individually:
R.I := 1;
R.F := 5.0;
However, we have to write R.all
when assigning to the whole record
R
.
Attributes
Finally, let's see an example of implicit dereference when using attributes:
with Ada.Text_IO; use Ada.Text_IO; procedure Show_Dereferencing is type Integer_Array is array (Positive range <>) of Integer; type Integer_Array_Access is access Integer_Array; Arr : constant Integer_Array_Access := new Integer_Array (1 .. 6); begin Put_Line ("Arr'First: " & Integer'Image (Arr'First)); Put_Line ("Arr'Last: " & Integer'Image (Arr'Last)); Put_Line ("Arr'Component_Size: " & Integer'Image (Arr'Component_Size)); Put_Line ("Arr.all'Component_Size: " & Integer'Image (Arr.all'Component_Size)); Put_Line ("Arr'Size: " & Integer'Image (Arr'Size)); Put_Line ("Arr.all'Size: " & Integer'Image (Arr.all'Size)); end Show_Dereferencing;
Here, we can write Arr'First
and Arr'Last
instead of
Arr.all'First
and Arr.all'Last
, respectively, because Arr
is implicitly dereferenced. The same applies to Arr'Component_Size
. Note
that we can write both Arr'Size
and Arr.all'Size
, but they have
different meanings:
Arr'Size
is the size of the access object; whileArr.all'Size
indicates the size of the actual arrayArr
.
In other words, the Size
attribute is not implicitly dereferenced.
In fact, any attribute that could potentially be ambiguous is not implicitly
dereferenced. Therefore, in those cases, we must explicitly indicate (by using
.all
or not) how we want to use the attribute.
Summary
The following table summarizes all instances where implicit dereferencing is supported:
Entities |
Standard Usage |
Implicit Dereference |
---|---|---|
Array components |
Arr.all (I) |
Arr (I) |
Array slices |
Arr.all (F .. L) |
Arr (F .. L) |
Record components |
Rec.all.C |
Rec.C |
Array attributes |
Arr.all’First |
Arr’First |
Arr.all’First (N) |
Arr’First (N) |
|
Arr.all’Last |
Arr’Last |
|
Arr.all’Last (N) |
Arr’Last (N) |
|
Arr.all’Range |
Arr’Range |
|
Arr.all’Range (N) |
Arr’Range (N) |
|
Arr.all’Length |
Arr’Length |
|
Arr.all’Length (N) |
Arr’Length (N) |
|
Arr.all’Component_Size |
Arr’Component_Size |
|
Task attributes |
T.all'Identity |
T'Identity |
T.all'Storage_Size |
T'Storage_Size |
|
T.all'Terminated |
T'Terminated |
|
T.all'Callable |
T'Callable |
|
Tagged type attributes |
X.all’Tag |
X’Tag |
Other attributes |
X.all'Valid |
X'Valid |
X.all'Old |
X'Old |
|
A.all’Constrained |
A’Constrained |
In the Ada Reference Manual
Ragged arrays
Ragged arrays — also known as jagged arrays — are non-uniform, multidimensional arrays. They can be useful to implement tables with varying number of coefficients, as we discuss as an example in this section.
Uniform multidimensional arrays
Consider an algorithm that processes data based on coefficients that depends on a selected quality level:
Quality level |
Number of coefficients |
#1 |
#2 |
#3 |
#4 |
#5 |
---|---|---|---|---|---|---|
Simplified |
1 |
0.15 |
||||
Better |
3 |
0.02 |
0.16 |
0.27 |
||
Best |
5 |
0.01 |
0.08 |
0.12 |
0.20 |
0.34 |
(Note that this is just a bogus table with no real purpose, as we're not trying to implement any actual algorithm.)
We can implement this table as a two-dimensional array (Calc_Table
),
where each quality level has an associated array:
package Data_Processing is type Quality_Level is (Simplified, Better, Best); private Calc_Table : constant array (Quality_Level, 1 .. 5) of Float := (Simplified => (0.15, 0.00, 0.00, 0.00, 0.00), Better => (0.02, 0.16, 0.27, 0.00, 0.00), Best => (0.01, 0.08, 0.12, 0.20, 0.34)); Last : constant array (Quality_Level) of Positive := (Simplified => 1, Better => 3, Best => 5); end Data_Processing;
Note that, in this implementation, we have a separate table Last
that
indicates the actual number of coefficients of each quality level.
Alternatively, we could use a record (Table_Coefficient
) that stores the
number of coefficients and the actual coefficients:
package Data_Processing is type Quality_Level is (Simplified, Better, Best); type Data is array (Positive range <>) of Float; private type Table_Coefficient is record Last : Positive; Coef : Data (1 .. 5); end record; Calc_Table : constant array (Quality_Level) of Table_Coefficient := (Simplified => (1, (0.15, 0.00, 0.00, 0.00, 0.00)), Better => (3, (0.02, 0.16, 0.27, 0.00, 0.00)), Best => (5, (0.01, 0.08, 0.12, 0.20, 0.34))); end Data_Processing;
In this case, we have a unidimensional array where each component (of
Table_Coefficient
type) contains an array (Coef
) with the
coefficients.
This is an example of a Process
procedure that references the
Calc_Table
:
package Data_Processing.Operations is procedure Process (D : in out Data; Q : Quality_Level); end Data_Processing.Operations;package body Data_Processing.Operations is procedure Process (D : in out Data; Q : Quality_Level) is begin for I in D'Range loop for J in 1 .. Calc_Table (Q).Last loop -- ... * Calc_Table (Q).Coef (J) null; end loop; -- D (I) := ... null; end loop; end Process; end Data_Processing.Operations;
Note that, to loop over the coefficients, we're using
for J in 1 .. Calc_Table (Q).Last loop
instead of
for J in Calc_Table (Q)'Range loop
. As we're trying to make a
non-uniform array fit in a uniform array, we cannot simply loop over all
elements using the Range
attribute, but must be careful to use the
correct number of elements in the loop instead.
Also, note that Calc_Table
has 15 coefficients in total. Out of those
coefficients, 6 coefficients (or 40 percent of the table) aren't being used.
Naturally, this is wasted memory space. We can improve this by using ragged
arrays.
Non-uniform multidimensional array
Ragged arrays are declared by using an access type to an array. By doing that, each array can be declared with a different size, thereby creating a non-uniform multidimensional array.
For example, we can declare a constant array Table
as a ragged array:
package Data_Processing is type Integer_Array is array (Positive range <>) of Integer; private type Integer_Array_Access is access constant Integer_Array; Table : constant array (1 .. 3) of Integer_Array_Access := (1 => new Integer_Array'(1 => 15), 2 => new Integer_Array'(1 => 12, 2 => 15, 3 => 20), 3 => new Integer_Array'(1 => 12, 2 => 15, 3 => 20, 4 => 20, 5 => 25, 6 => 30)); end Data_Processing;
Here, each component of Table
is an access to another array. As each
array is allocated via new
, those arrays may have different sizes.
We can rewrite the example from the previous subsection using a ragged array
for the Calc_Table
:
package Data_Processing is type Quality_Level is (Simplified, Better, Best); type Data is array (Positive range <>) of Float; private type Coefficients is access constant Data; Calc_Table : constant array (Quality_Level) of Coefficients := (Simplified => new Data'(1 => 0.15), Better => new Data'(0.02, 0.16, 0.27), Best => new Data'(0.01, 0.08, 0.12, 0.20, 0.34)); end Data_Processing;
Now, we aren't wasting memory space because each data component has the right
size that is required for each quality level. Also, we don't need to store the
number of coefficients, as this information is automatically available from the
array initialization — via the allocation of the Data
array for
the Coefficients
type.
Note that the Coefficients
type is defined as access constant
.
We discuss access-to-constant types
in more details later on.
This is the adapted Process
procedure:
package Data_Processing.Operations is procedure Process (D : in out Data; Q : Quality_Level); end Data_Processing.Operations;package body Data_Processing.Operations is procedure Process (D : in out Data; Q : Quality_Level) is begin for I in D'Range loop for J in Calc_Table (Q)'Range loop -- ... * Calc_Table (Q).Coef (J) null; end loop; -- D (I) := ... null; end loop; end Process; end Data_Processing.Operations;
Now, we can simply loop over the coefficients by writing
for J in Calc_Table (Q)'Range loop
, as each element of Calc_Table
automatically has the correct range.
Aliasing
The term aliasing
refers to objects in memory that we can access using more than a single
reference. In Ada, if we allocate an object via new
, we have a
potentially aliased object. We can then have multiple references to this
object:
with Ada.Text_IO; use Ada.Text_IO; procedure Show_Aliasing is type Integer_Access is access Integer; A1, A2 : Integer_Access; begin A1 := new Integer; A2 := A1; A1.all := 22; Put_Line ("A1: " & Integer'Image (A1.all)); Put_Line ("A2: " & Integer'Image (A2.all)); A2.all := 24; Put_Line ("A1: " & Integer'Image (A1.all)); Put_Line ("A2: " & Integer'Image (A2.all)); end Show_Aliasing;
In this example, we access the object allocated via new
by using either
A1
or A2
, as both refer to the same aliased object. In other
words, A1
or A2
allow us to access the same object in memory.
Important
Note that aliasing is unrelated to renaming. For example, we could use renaming to write a program that looks similar to the one above:
with Ada.Text_IO; use Ada.Text_IO; procedure Show_Renaming is A1 : Integer; A2 : Integer renames A1; begin A1 := 22; Put_Line ("A1: " & Integer'Image (A1)); Put_Line ("A2: " & Integer'Image (A2)); A2 := 24; Put_Line ("A1: " & Integer'Image (A1)); Put_Line ("A2: " & Integer'Image (A2)); end Show_Renaming;
Here, A1
or A2
are two different names for the same object.
However, the object itself isn't aliased.
In the Ada Reference Manual
Aliased objects
As we discussed previously, we use
new
to create aliased objects on the heap. We can also use general
access types to access objects that were created on the stack.
By default, objects created on the stack aren't aliased. Therefore, we have to
indicate that an object is aliased by using the aliased
keyword in the
object's declaration: Obj : aliased Integer;
.
Let's see an example:
with Ada.Text_IO; use Ada.Text_IO; procedure Show_Aliased_Obj is type Integer_Access is access all Integer; I_Var : aliased Integer; A1 : Integer_Access; begin A1 := I_Var'Access; A1.all := 22; Put_Line ("A1: " & Integer'Image (A1.all)); end Show_Aliased_Obj;
Here, we declare I_Var
as an aliased integer variable and get a
reference to it, which we assign to A1
. Naturally, we could also have
two accesses A1
and A2
:
with Ada.Text_IO; use Ada.Text_IO; procedure Show_Aliased_Obj is type Integer_Access is access all Integer; I_Var : aliased Integer; A1, A2 : Integer_Access; begin A1 := I_Var'Access; A2 := A1; A1.all := 22; Put_Line ("A1: " & Integer'Image (A1.all)); Put_Line ("A2: " & Integer'Image (A2.all)); A2.all := 24; Put_Line ("A1: " & Integer'Image (A1.all)); Put_Line ("A2: " & Integer'Image (A2.all)); end Show_Aliased_Obj;