Subprograms

Parameter Modes and Associations

In this section, we discuss some details about parameter modes and associations. First of all, as we know, parameters can be either formal or actual:

  • Formal parameters are the ones we see in a subprogram declaration and implementation;

  • Actual parameters are the ones we see in a subprogram call.

    • Note that actual parameters are also called subprogram arguments in other languages.

We define parameter associations as the connection between an actual parameter in a subprogram call and its declaration as a formal parameter in a subprogram specification or body.

Formal Parameter Modes

We already discussed formal parameter modes in the Introduction to Ada course:

in

Parameter can only be read, not written

out

Parameter can be written to, then read

in out

Parameter can be both read and written

As this topic was already discussed in that course — and we used parameter modes extensively in all code examples from that course —, we won't introduce the topic again here. Instead, we'll look into some of the more advanced details.

By-copy and by-reference

In the Introduction to Ada course, we saw that parameter modes don't correspond directly to how parameters are actually passed. In fact, an in out parameter could be passed by copy. For example:

    
    
    
        
with System; procedure Check_Param_Passing (Formal : System.Address; Actual : System.Address);
with Ada.Text_IO; use Ada.Text_IO; with System.Address_Image; procedure Check_Param_Passing (Formal : System.Address; Actual : System.Address) is begin Put_Line ("Formal parameter at " & System.Address_Image (Formal)); Put_Line ("Actual parameter at " & System.Address_Image (Actual)); if System.Address_Image (Formal) = System.Address_Image (Actual) then Put_Line ("Parameter is passed by reference."); else Put_Line ("Parameter is passed by copy."); end if; end Check_Param_Passing;
with System; package Machine_X is procedure Update_Value (V : in out Integer; AV : System.Address); end Machine_X;
with Check_Param_Passing; package body Machine_X is procedure Update_Value (V : in out Integer; AV : System.Address) is begin V := V + 1; Check_Param_Passing (Formal => V'Address, Actual => AV); end Update_Value; end Machine_X;
with Machine_X; use Machine_X; procedure Show_By_Copy_By_Ref_Params is A : Integer := 5; begin Update_Value (A, A'Address); end Show_By_Copy_By_Ref_Params;

As we can see by running this example,

  • the integer variable A in the Show_By_Copy_By_Ref_Params procedure

and

  • the V parameter in the Update_Value procedure

have different addresses, so they are different objects. Therefore, we conclude that this parameter is being passed by value, even though it has the in out mode. (We talk more about addresses and the 'Address attribute later on).

As we know, when a parameter is passed by copy, it is first copied to a temporary object. In the case of a parameter with in out mode, the temporary object is copied back to the original (actual) parameter at the end of the subprogram call. In our example, the temporary object indicated by V is copied back to A at the end of the call to Update_Value.

In Ada, it's not the parameter mode that determines whether a parameter is passed by copy or by reference, but rather its type. We can distinguish between three categories:

  1. By-copy types;

  2. By-reference types;

  3. Unspecified types.

Obviously, parameters of by-copy types are passed by copy and parameters of by-reference type are passed by reference. However, if a category isn't specified — i.e. when the type is neither a by-copy nor a by-reference type —, the decision is essentially left to the compiler.

As a rule of thumb, we can say that;

  • elementary types — and any type that is essentially elementary, such as a private type whose full view is an elementary type — are passed by copy;

  • tagged and explicitly limited types — and other types that are essentially tagged, such as task types — are passed by reference.

The following table provides more details:

Type category

Parameter passing

List of types

By copy

By copy

  • Elementary types

  • Descendant of a private type whose full type is a by-copy type

By reference

By reference

  • Tagged types

  • Task and protected types

  • Explicitly limited record types

  • Composite types with at least one subcomponent of a by-reference type

  • Private types whose full type is a by-reference type

  • Any descendant of the types mentioned above

Unspecified

Either by copy or by reference

  • Any type not mentioned above

Note that, for parameters of limited types, only those parameters whose type is explicitly limited are always passed by reference. We discuss this topic in more details in another chapter.

Let's see an example:

    
    
    
        
with System; package Machine_X is type Integer_Array is array (Positive range <>) of Integer; type Rec is record A : Integer; end record; type Rec_Array is record A : Integer; Arr : Integer_Array (1 .. 100); end record; type Tagged_Rec is tagged record A : Integer; end record; procedure Update_Value (R : in out Rec; AR : System.Address); procedure Update_Value (RA : in out Rec_Array; ARA : System.Address); procedure Update_Value (R : in out Tagged_Rec; AR : System.Address); end Machine_X;
with Check_Param_Passing; package body Machine_X is procedure Update_Value (R : in out Rec; AR : System.Address) is begin R.A := R.A + 1; Check_Param_Passing (Formal => R'Address, Actual => AR); end Update_Value; procedure Update_Value (RA : in out Rec_Array; ARA : System.Address) is begin RA.A := RA.A + 1; Check_Param_Passing (Formal => RA'Address, Actual => ARA); end Update_Value; procedure Update_Value (R : in out Tagged_Rec; AR : System.Address) is begin R.A := R.A + 1; Check_Param_Passing (Formal => R'Address, Actual => AR); end Update_Value; end Machine_X;
with Ada.Text_IO; use Ada.Text_IO; with Machine_X; use Machine_X; procedure Show_By_Copy_By_Ref_Params is TR : Tagged_Rec := (A => 5); R : Rec := (A => 5); RA : Rec_Array := (A => 5, Arr => (others => 0)); begin Put_Line ("Tagged record"); Update_Value (TR, TR'Address); Put_Line ("Untagged record"); Update_Value (R, R'Address); Put_Line ("Untagged record with array"); Update_Value (RA, RA'Address); end Show_By_Copy_By_Ref_Params;

When we run this example, we see that the object of tagged type (Tagged_Rec) is passed by reference to the Update_Value procedure. In the case of the objects of untagged record types, you might see this:

  • the parameter of Rec type — which is an untagged record with a single component of integer type —, the parameter is passed by copy;

  • the parameter of Rec_Array type — which is an untagged record with a large array of 100 components —, the parameter is passed by reference.

Because Rec and Rec_Array are neither by-copy nor by-reference types, the decision about how to pass them to the Update_Value procedure is made by the compiler. (Thus, it is possible that you see different results when running the code above.)

Bounded errors

When we use parameters of types that are neither by-copy nor by-reference types, we might encounter the situation where we have the same object bound to different names in a subprogram. For example, if:

  • we use a global object Global_R of a record type Rec

and

  • we have a subprogram with an in-out parameter of the same record type Rec

and

  • we pass Global_R as the actual parameter for the in-out parameter of this subprogram,

then we have two access paths to this object: one of them using the global variable directly, and the other one using it indirectly via the in-out parameter. This situation could lead to undefined behavior or to a program error. Consider the following code example:

    
    
    
        
with System; package Machine_X is type Rec is record A : Integer; end record; Global_R : Rec := (A => 0); procedure Update_Value (R : in out Rec; AR : System.Address); end Machine_X;
with Ada.Text_IO; use Ada.Text_IO; with Check_Param_Passing; package body Machine_X is procedure Update_Value (R : in out Rec; AR : System.Address) is procedure Show_Vars is begin Put_Line ("Global_R.A: " & Integer'Image (Global_R.A)); Put_Line ("R.A: " & Integer'Image (R.A)); end Show_Vars; begin Check_Param_Passing (Formal => R'Address, Actual => AR); Put_Line ("Incrementing Global_R.A..."); Global_R.A := Global_R.A + 1; Show_Vars; Put_Line ("Incrementing R.A..."); R.A := R.A + 5; Show_Vars; end Update_Value; end Machine_X;
with Ada.Text_IO; use Ada.Text_IO; with Machine_X; use Machine_X; procedure Show_By_Copy_By_Ref_Params is begin Put_Line ("Calling Update_Value..."); Update_Value (Global_R, Global_R'Address); Put_Line ("After call to Update_Value..."); Put_Line ("Global_R.A: " & Integer'Image (Global_R.A)); end Show_By_Copy_By_Ref_Params;

In the Update_Value procedure, because Global_R and R have a type that is neither a by-pass nor a by-reference type, the language does not specify whether the old or the new value would be read in the calls to Put_Line. In other words, the actual behavior is undefined. Also, this situation might raise the Program_Error exception.

Important

As a general advice:

  • you should be very careful when using global variables and

  • you should avoid passing them as parameters in situations such as the one illustrated in the code example above.

Aliased parameters

When a parameter is specified as aliased, it is always passed by reference, independently of the type we're using. In this sense, we can use this keyword to circumvent the rules mentioned so far. (We discuss more about aliasing and aliased parameters later on.)

Let's rewrite a previous code example that has a parameter of elementary type and change it to aliased:

    
    
    
        
with System; package Machine_X is procedure Update_Value (V : aliased in out Integer; AV : System.Address); end Machine_X;
with Check_Param_Passing; package body Machine_X is procedure Update_Value (V : aliased in out Integer; AV : System.Address) is begin V := V + 1; Check_Param_Passing (Formal => V'Address, Actual => AV); end Update_Value; end Machine_X;
with Machine_X; use Machine_X; procedure Show_By_Copy_By_Ref_Params is A : aliased Integer := 5; begin Update_Value (A, A'Address); end Show_By_Copy_By_Ref_Params;

As we can see, A is now passed by reference.

Note that we can only pass aliased objects to aliased parameters. If we try to pass a non-aliased object, we get a compilation error:

    
    
    
        
with Machine_X; use Machine_X; procedure Show_By_Copy_By_Ref_Params is A : Integer := 5; begin Update_Value (A, A'Address); end Show_By_Copy_By_Ref_Params;

Again, we discuss more about aliased parameters and aliased objects later on in the context of access types.

Parameter Associations

When actual parameters are associated with formal parameters, some rules are checked. As a typical example, the type of each actual parameter must match the type of the corresponding actual parameter. In this section, we see some details about how this association is made and some of the potential errors.

In the Ada Reference Manual

Parameter order and association

As we already know, when calling subprograms, we can use positional or named parameter association — or a mixture of both. Also, parameters can have default values. Let's see some examples:

    
    
    
        
package Operations is procedure Add (Left : in out Integer; Right : Float := 1.0); end Operations;
package body Operations is procedure Add (Left : in out Integer; Right : Float := 1.0) is begin Left := Left + Integer (Right); end Add; end Operations;
with Operations; use Operations; procedure Show_Param_Association is A : Integer := 5; begin -- Positional association Add (A, 2.0); -- Positional association -- (using default value) Add (A); -- Named association Add (Left => A, Right => 2.0); -- Named association (inversed order) Add (Right => 2.0, Left => A); -- Mixed positional / named association Add (A, Right => 2.0); end Show_Param_Association;

This code snippet has examples of positional and name parameter association. Also, it has an example of mixed positional / named parameter association. In most cases, the actual A parameter is associated with the formal Left parameter, and the actual 2.0 parameter is associated with the formal Right parameter.

In addition to that, parameters can have default values, so, when we write Add (A), the A variable is associated with the Left parameter and the default value (1.0) is associated with the Right parameter.

Also, when we use named parameter association, the parameter order is irrelevant: we can, for example, write the last parameter as the first one. Therefore, we can write Add (Right => 2.0, Left => A) instead of Add (Left => A, Right => 2.0).

Ambiguous calls

Ambiguous calls can be detected by the compiler during parameter association. For example, when we have both default values in parameters and subprogram overloading, the compiler might be unable to decide which subprogram we're calling:

    
    
    
        
package Operations is procedure Add (Left : in out Integer); procedure Add (Left : in out Integer; Right : Float := 1.0); end Operations;
package body Operations is procedure Add (Left : in out Integer) is begin Left := Left + 1; end Add; procedure Add (Left : in out Integer; Right : Float := 1.0) is begin Left := Left + Integer (Right); end Add; end Operations;
with Operations; use Operations; procedure Show_Param_Association is A : Integer := 5; begin Add (A); -- ERROR: cannot decide which -- procedure to take end Show_Param_Association;

As we see in this example, the Add procedure is overloaded. The first instance has one parameter, and the second instance has two parameters, where the second parameter has a default value. When we call Add with just one parameter, the compiler cannot decide whether we intend to call

  • the first instance of Add with one parameter

or

  • the second instance of Add using the default value for the second parameter.

In this specific case, there are multiple options to solve the issue, but all of them involve redesigning the package specification:

  • we could just rename one of Add procedures (thereby eliminating the subprogram overloading);

  • we could rename the first parameter of one of the Add procedures and use named parameter association in the call to the procedure;

    • For example, we could rename the parameter to Value and call Add (Value => A).

  • remove the default value from the second parameter of the second instance of Add.

Overlapping actual parameters

When we have more than one out or in out parameters in a subprogram, we might run into the situation where the actual parameter overlaps with another parameter. For example:

    
    
    
        
package Machine_X is procedure Update_Value (V1 : in out Integer; V2 : out Integer); end Machine_X;
package body Machine_X is procedure Update_Value (V1 : in out Integer; V2 : out Integer) is begin V1 := V1 + 1; V2 := V2 + 1; end Update_Value; end Machine_X;
with Machine_X; use Machine_X; procedure Show_By_Copy_By_Ref_Params is A : Integer := 5; begin Update_Value (A, A); end Show_By_Copy_By_Ref_Params;

In this case, we're using A for both output parameters in the call to Update_Value. Passing one variable to more than one output parameter in a given call is forbidden in Ada, so this triggers a compilation error. Depending on the specific context, you could solve this issue by using temporary variables for the other output parameters.

Operators

Operators are commonly used for variables of scalar types such as Integer and Float. In these cases, they replace usual function calls. (To be more precise, operators are function calls, but written in a different format.) For example, we simply write A := A + B + C; when we want to add three integer variables. A hypothetical, non-intuitive version of this operation could be A := Add (Add (A, B), C);. In such cases, operators allow for expressing function calls in a more intuitive way.

Many primitive operators exist for scalar types. We classify them as follows:

Category

Operators

Logical

and, or, xor

Relational

=, /=, <, <=, >, >=

Unary adding

+, -

Binary adding

+, -, &

Multiplying

*, /, mod, rem

Highest precedence

**, abs, not

In the Ada Reference Manual

User-defined operators

For non-scalar types, not all operators are defined. For example, it wouldn't make sense to expect a compiler to include an addition operator for a record type with multiple components. Exceptions to this rule are the equality and inequality operators (= and /=), which are defined for any type (be it scalar, record types, and array types).

For array types, the concatenation operator (&) is a primitive operator:

    
    
    
        
package Integer_Arrays is type Integer_Array is array (Positive range <>) of Integer; end Integer_Arrays;
with Ada.Text_IO; use Ada.Text_IO; with Integer_Arrays; use Integer_Arrays; procedure Show_Array_Concatenation is A, B : Integer_Array (1 .. 5); R : Integer_Array (1 .. 10); begin A := (1 & 2 & 3 & 4 & 5); B := (6 & 7 & 8 & 9 & 10); R := A & B; for E of R loop Put (E'Image & ' '); end loop; New_Line; end Show_Array_Concatenation;

In this example, we're using the primitive & operator to concatenate the A and B arrays in the assignment to R. Similarly, we're concatenating individual components (integer values) to create an aggregate that we assign to A and B.

In contrast to this, the addition operator is not available for arrays:

    
    
    
        
package Integer_Arrays is type Integer_Array is array (Positive range <>) of Integer; end Integer_Arrays;
with Ada.Text_IO; use Ada.Text_IO; with Integer_Arrays; use Integer_Arrays; procedure Show_Array_Addition is A, B, R : Integer_Array (1 .. 5); begin A := (1 & 2 & 3 & 4 & 5); B := (6 & 7 & 8 & 9 & 10); R := A + B; for E of R loop Put (E'Image & ' '); end loop; New_Line; end Show_Array_Addition;

We can, however, define custom operators for any type. For example, if a specific type doesn't have a predefined addition operator, we can define our own + operator for it.

Note that we're limited to the operator symbols that are already defined by the Ada language (see the previous table for the complete list of operators). In other words, the operator we define must be selected from one of those existing symbols; we cannot use new symbols for custom operators.

In other languages

Some programming languages — such as Haskell — allow you to define and use custom operator symbols. For example, in Haskell, you can create a new "broken bar" (¦) operator for integer values:

(¦) :: Int -> Int -> Int
a ¦ b = a + a + b

main = putStrLn $ show (2 ¦ 3)

This is not possible in Ada.

Let's define a custom addition operator that adds individual components of the Integer_Array type:

    
    
    
        
package Integer_Arrays is type Integer_Array is array (Positive range <>) of Integer; function "+" (Left, Right : Integer_Array) return Integer_Array with Post => (for all I in "+"'Result'Range => "+"'Result (I) = Left (I) + Right (I)); end Integer_Arrays;
package body Integer_Arrays is function "+" (Left, Right : Integer_Array) return Integer_Array is R : Integer_Array (Left'Range); begin for I in Left'Range loop R (I) := Left (I) + Right (I); end loop; return R; end "+"; end Integer_Arrays;
with Ada.Text_IO; use Ada.Text_IO; with Integer_Arrays; use Integer_Arrays; procedure Show_Array_Addition is A, B, R : Integer_Array (1 .. 5); begin A := (1 & 2 & 3 & 4 & 5); B := (6 & 7 & 8 & 9 & 10); R := A + B; for E of R loop Put (E'Image & ' '); end loop; New_Line; end Show_Array_Addition;

Now, the R := A + B line doesn't trigger a compilation error anymore because the + operator is defined for the Integer_Array type.

In the implementation of the +, we return an array with the range of the Left array where each component is the sum of the Left and Right arrays. In the declaration of the + operator, we're defining the expected behavior in the postcondition. Here, we're saying that, for each index of the resulting array (for all I in "+"'Result'Range), the value of each component of the resulting array at that specific index is the sum of the components from the Left and Right arrays at the same index ("+"'Result (I) = Left (I) + Right (I)). (for all denotes a quantified expression.)

Note that, in this implementation, we assume that the range of Right is a subset of the range of Left. If that is not the case, the Constraint_Error exception will be raised at runtime in the loop. (You can test this by declaring B as Integer_Array (5 .. 10), for example.)

We can also define custom operators for record types. For example, we could declare two + operators for a record containing the name and address of a person:

    
    
    
        
package Addresses is type Person is private; function "+" (Name : String; Address : String) return Person; function "+" (Left, Right : Person) return Person; procedure Display (P : Person); private subtype Name_String is String (1 .. 40); subtype Address_String is String (1 .. 100); type Person is record Name : Name_String; Address : Address_String; end record; end Addresses;
with Ada.Strings.Fixed; use Ada.Strings.Fixed; with Ada.Text_IO; use Ada.Text_IO; package body Addresses is function "+" (Name : String; Address : String) return Person is begin return (Name => Head (Name, Name_String'Length), Address => Head (Address, Address_String'Length)); end "+"; function "+" (Left, Right : Person) return Person is begin return (Name => Left.Name, Address => Right.Address); end "+"; procedure Display (P : Person) is begin Put_Line ("Name: " & P.Name); Put_Line ("Address: " & P.Address); New_Line; end Display; end Addresses;
with Ada.Text_IO; use Ada.Text_IO; with Addresses; use Addresses; procedure Show_Address_Addition is John : Person := "John" + "4 Main Street"; Jane : Person := "Jane" + "7 High Street"; begin Display (John); Display (Jane); Put_Line ("----------------"); Jane := Jane + John; Display (Jane); end Show_Address_Addition;

In this example, the first + operator takes two strings — with the name and address of a person — and returns an object of Person type. We use this operator to initialize the John and Jane variables.

The second + operator in this example brings two people together. Here, the person on the left side of the + operator moves to the home of the person on the right side. In this specific case, Jane is moving to John's house.

As a small remark, we usually expect that the + operator is commutative. In other words, changing the order of the elements in the operation doesn't change the result. However, in our definition above, this is not the case, as we can confirm by comparing the operation in both orders:

    
    
    
        
with Ada.Text_IO; use Ada.Text_IO; with Addresses; use Addresses; procedure Show_Address_Addition is John : constant Person := "John" + "4 Main Street"; Jane : constant Person := "Jane" + "7 High Street"; begin if Jane + John = John + Jane then Put_Line ("It's commutative!"); else Put_Line ("It's not commutative!"); end if; end Show_Address_Addition;

In this example, we're using the primitive = operator for the Person to assess whether the result of the addition is commutative.

In the Ada Reference Manual

Expression functions

Usually, we implement Ada functions with a construct like this: begin return X; end;. In other words, we create a begin ... end; block and we have at least one return statement in that block. An expression function, in contrast, is a function that is implemented with a simple expression in parentheses, such as (X);. In this case, we don't use a begin ... end; block or a return statement.

As an example of an expression, let's say we want to implement a function named Is_Zero that checks if the value of the integer parameter I is zero. We can implement this function with the expression I = 0. In the usual approach, we would create the implementation by writing is begin return I = 0; end Is_Zero;. When using expression functions, however, we can simplify the implementation by just writing is (I = 0);. This is the complete code of Is_Zero using an expression function:

    
    
    
        
package Expr_Func is function Is_Zero (I : Integer) return Boolean is (I = 0); end Expr_Func;

An expression function has the same effect as the usual version using a block. In fact, the code above is similar to this implementation of the Is_Zero function using a block:

    
    
    
        
package Expr_Func is function Is_Zero (I : Integer) return Boolean; end Expr_Func;
package body Expr_Func is function Is_Zero (I : Integer) return Boolean is begin return I = 0; end Is_Zero; end Expr_Func;

The only difference between these two versions of the Expr_Func packages is that, in the first version, the package specification contains the implementation of the Is_Zero function, while, in the second version, the implementation is in the body of the Expr_Func package.

An expression function can be, at same time, the specification and the implementation of a function. Therefore, in the first version of the Expr_Func package above, we don't have a separate implementation of the Is_Zero function because (I = 0) is the actual implementation of the function. Note that this is only possible for expression functions; you cannot have a function implemented with a block in a package specification. For example, the following code is wrong and won't compile:

    
    
    
        
package Expr_Func is function Is_Zero (I : Integer) return Boolean is begin return I = 0; end Is_Zero; end Expr_Func;

We can, of course, separate the function declaration from its implementation as an expression function. For example, we can rewrite the first version of the Expr_Func package and move the expression function to the body of the package:

    
    
    
        
package Expr_Func is function Is_Zero (I : Integer) return Boolean; end Expr_Func;
package body Expr_Func is function Is_Zero (I : Integer) return Boolean is (I = 0); end Expr_Func;

In addition, we can use expression functions in the private part of a package specification. For example, the following code declares the Is_Valid function in the specification of the My_Data package, while its implementation is an expression function in the private part of the package specification:

    
    
    
        
package My_Data is type Data is private; function Is_Valid (D : Data) return Boolean; private type Data is record Valid : Boolean; end record; function Is_Valid (D : Data) return Boolean is (D.Valid); end My_Data;

Naturally, we could write the function implementation in the package body instead:

    
    
    
        
package My_Data is type Data is private; function Is_Valid (D : Data) return Boolean; private type Data is record Valid : Boolean; end record; end My_Data;
package body My_Data is function Is_Valid (D : Data) return Boolean is (D.Valid); end My_Data;

In the Ada Reference Manual

Overloading

Note

This section was originally written by Robert A. Duff and published as Gem #50: Overload Resolution.

Ada allows overloading of subprograms, which means that two or more subprogram declarations with the same name can be visible at the same place. Here, "name" can refer to operator symbols, like "+". Ada also allows overloading of various other notations, such as literals and aggregates.

In most languages that support overloading, overload resolution is done "bottom up" — that is, information flows from inner constructs to outer constructs. As usual, computer folks draw their trees upside-down, with the root at the top. For example, if we have two procedures Print:

    
    
    
        
procedure Show_Overloading is package Types is type Sequence is null record; type Set is null record; procedure Print (S : Sequence) is null; procedure Print (S : Set) is null; end Types; use Types; X : Sequence; begin -- Compiler selects Print (S : Sequence) Print (X); end Show_Overloading;

the type of X determines which Print is meant in the call.

Ada is unusual in that it supports top-down overload resolution as well:

    
    
    
        
procedure Show_Top_Down_Overloading is package Types is type Sequence is null record; type Set is null record; function Empty return Sequence is ((others => <>)); function Empty return Set is ((others => <>)); procedure Print_Sequence (S : Sequence) is null; procedure Print_Set (S : Set) is null; end Types; use Types; X : Sequence; begin -- Compiler selects function -- Empty return Sequence Print_Sequence (Empty); end Show_Top_Down_Overloading;

The type of the formal parameter S of Print_Sequence determines which Empty is meant in the call. In C++, for example, the equivalent of the Print (X) example would resolve, but the Print_Sequence (Empty) would be illegal, because C++ does not use top-down information.

If we overload things too heavily, we can cause ambiguities:

    
    
    
        
procedure Show_Overloading_Error is package Types is type Sequence is null record; type Set is null record; function Empty return Sequence is ((others => <>)); function Empty return Set is ((others => <>)); procedure Print (S : Sequence) is null; procedure Print (S : Set) is null; end Types; use Types; X : Sequence; begin Print (Empty); -- Illegal! end Show_Overloading_Error;

The call is ambiguous, and therefore illegal, because there are two possible meanings. One way to resolve the ambiguity is to use a qualified expression to say which type we mean:

Print (Sequence'(Empty));

Note that we're now using both bottom-up and top-down overload resolution: Sequence' determines which Empty is meant (top down) and which Print is meant (bottom up). You can qualify an expression, even if it is not ambiguous according to Ada rules — you might want to clarify the type because it might be ambiguous for human readers.

Of course, you could instead resolve the Print (Empty) example by modifying the source code so the names are unique, as in the earlier examples. That might well be the best solution, assuming you can modify the relevant sources. Too much overloading can be confusing. How much is "too much" is in part a matter of taste.

Ada really needs to have top-down overload resolution, in order to resolve literals. In some languages, you can tell the type of a literal by looking at it, for example appending L (letter el) means "the type of this literal is long int". That sort of kludge won't work in Ada, because we have an open-ended set of integer types:

    
    
    
        
procedure Show_Literal_Resolution is type Apple_Count is range 0 .. 100; procedure Peel (Count : Apple_Count) is null; begin Peel (20); end Show_Literal_Resolution;

You can't tell by looking at the literal 20 what its type is. The type of formal parameter Count tells us that 20 is an Apple_Count, as opposed to some other type, such as Standard.Long_Integer.

Technically, the type of 20 is universal_integer, which is implicitly converted to Apple_Count — it's really the result type of that implicit conversion that is at issue. But that's an obscure point — you won't go too far wrong if you think of the integer literal notation as being overloaded on all integer types.

Developers sometimes wonder why the compiler can't resolve something that seems obvious. For example:

    
    
    
        
procedure Show_Literal_Resolution_Error is type Apple_Count is range 0 .. 100; procedure Slice (Count : Apple_Count) is null; type Orange_Count is range 0 .. 10_000; procedure Slice (Count : Orange_Count) is null; begin Slice (Count => (10_000)); -- Illegal! end Show_Literal_Resolution_Error;

This call is ambiguous, and therefore illegal. But why? Clearly the developer must have meant the Orange_Count one, because 10_000 is out of range for Apple_Count. And all the relevant expressions happen to be static.

Well, a good rule of thumb in language design (for languages with overloading) is that the overload resolution rules should not be "too smart". We want this example to be illegal to avoid confusion on the part of developers reading the code. As usual, a qualified expression fixes it:

Slice (Count => Orange_Count'(10_000));

Another example, similar to the literal, is the aggregate. Ada uses a simple rule: the type of an aggregate is determined top down (i.e., from the context in which the aggregate appears). Bottom-up information is not used; that is, the compiler does not look inside the aggregate in order to determine its type.

    
    
    
        
procedure Show_Record_Resolution_Error is type Complex is record Re, Im : Float; end record; procedure Grind (X : Complex) is null; procedure Grind (X : String) is null; begin Grind (X => (Re => 1.0, Im => 1.0)); -- ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ -- Illegal! end Show_Record_Resolution_Error;

There are two Grind procedures visible, so the type of the aggregate could be Complex or String, so it is ambiguous and therefore illegal. The compiler is not required to notice that there is only one type with components Re and Im, of some real type — in fact, the compiler is not allowed to notice that, for overloading purposes.

We can qualify as usual:

Grind (X => Complex'(Re => 1.0, Im => 1.0));

Only after resolving that the type of the aggregate is Complex can the compiler look inside and make sure Re and Im make sense.

This not-too-smart rule for aggregates helps prevent confusion on the part of developers reading the code. It also simplifies the compiler, and makes the overload resolution algorithm reasonably efficient.

Operator Overloading

We've seen previously that we can define custom operators for any type. We've also seen that subprograms can be overloaded. Since operators are functions, we're essentially talking about operator overloading, as we're defining the same operator (say + or -) for different types.

As another example of operator overloading, in the Ada standard library, operators are defined for the Complex type of the Ada.Numerics.Generic_Complex_Types package. This package contains not only the definition of the + operator for two objects of Complex type, but also for combination of Complex and other types. For instance, we can find these declarations:

function "+" (Left, Right : Complex)
              return Complex;
function "+" (Left : Complex;   Right : Real'Base)
              return Complex;
function "+" (Left : Real'Base; Right : Complex)
              return Complex;

This example shows that the + operator — as well as other operators — are being overloaded in the Generic_Complex_Types package.

Operator Overriding

We can also override operators of derived types. This allows for modifying the behavior of operators for the corresponding derived types.

To override an operator of a derived type, we simply implement a function for that operator. This is the same as how we implement custom operators (as we've seen previously).

As an example, when adding two fixed-point values, the result might be out of range, which causes an exception to be raised. A common strategy to avoid exceptions in this case is to saturate the resulting value. This strategy is typically employed in signal processing algorithms, for example.

In this example, we declare and use the 32-bit fixed-point type TQ31:

    
    
    
        
package Fixed_Point is D : constant := 2.0 ** (-31); type TQ31 is delta D range -1.0 .. 1.0 - D; end Fixed_Point;
with Ada.Text_IO; use Ada.Text_IO; with Fixed_Point; use Fixed_Point; procedure Show_Sat_Op is A, B, C : TQ31; begin A := TQ31'Last; B := TQ31'Last; C := A + B; Put_Line (A'Image & " + " & B'Image & " = " & C'Image); A := TQ31'First; B := TQ31'First; C := A + B; Put_Line (A'Image & " + " & B'Image & " = " & C'Image); end Show_Sat_Op;

Here, we're using the standard + operator, which raises a Constraint_Error exception in the C := A + B; statement due to an overflow. Let's now override the addition operator and enforce saturation when the result is out of range:

    
    
    
        
package Fixed_Point is D : constant := 2.0 ** (-31); type TQ31 is delta D range -1.0 .. 1.0 - D; function "+" (Left, Right : TQ31) return TQ31; end Fixed_Point;
package body Fixed_Point is function "+" (Left, Right : TQ31) return TQ31 is type TQ31_2 is delta TQ31'Delta range TQ31'First * 2.0 .. TQ31'Last * 2.0; L : constant TQ31_2 := TQ31_2 (Left); R : constant TQ31_2 := TQ31_2 (Right); Res : TQ31_2; begin Res := L + R; if Res > TQ31_2 (TQ31'Last) then return TQ31'Last; elsif Res < TQ31_2 (TQ31'First) then return TQ31'First; else return TQ31 (Res); end if; end "+"; end Fixed_Point;
with Ada.Text_IO; use Ada.Text_IO; with Fixed_Point; use Fixed_Point; procedure Show_Sat_Op is A, B, C : TQ31; begin A := TQ31'Last; B := TQ31'Last; C := A + B; Put_Line (A'Image & " + " & B'Image & " = " & C'Image); A := TQ31'First; B := TQ31'First; C := A + B; Put_Line (A'Image & " + " & B'Image & " = " & C'Image); end Show_Sat_Op;

In the implementation of the overridden + operator of the TQ31 type, we declare another type (TQ31_2) with a wider range than TQ31. We use variables of the TQ31_2 type to perform the actual addition, and then we verify whether the result is still in TQ31's range. If it is, we simply convert the result back to the TQ31 type. Otherwise, we saturate it — using either the first or last value of the TQ31 type.

When overriding operators, the overridden operator replaces the original one. For example, in the A + B operation of the Show_Sat_Op procedure above, we're using the overridden version of the + operator, which performs saturation. Therefore, this operation doesn't raise an exception (as it was the case with the original + operator).

Nonreturning procedures

Usually, when calling a procedure P, we expect that it returns to the caller's thread of control after performing some action in the body of P. However, there are situations where a procedure never returns. We can indicate this fact by using the No_Return aspect in the subprogram declaration.

A typical example is that of a server that is designed to run forever until the process is killed or the machine where the server runs is switched off. This server can be implemented as an endless loop. For example:

    
    
    
        
package Servers is procedure Run_Server with No_Return; end Servers;
package body Servers is procedure Run_Server is begin pragma Warnings (Off, "implied return after this statement"); while True loop -- Processing happens here... null; end loop; end Run_Server; end Servers;
with Servers; use Servers; procedure Show_Endless_Loop is begin Run_Server; end Show_Endless_Loop;

In this example, Run_Server doesn't exit from the while True loop, so it never returns to the Show_Endless_Loop procedure.

The same situation happens when we call a procedure that raises an exception unconditionally. In that case, exception handling is triggered, so that the procedure never returns to the caller. An example is that of a logging procedure that writes a message before raising an exception internally:

    
    
    
        
package Loggers is Logged_Failure : exception; procedure Log_And_Raise (Msg : String) with No_Return; end Loggers;
with Ada.Text_IO; use Ada.Text_IO; package body Loggers is procedure Log_And_Raise (Msg : String) is begin Put_Line (Msg); raise Logged_Failure; end Log_And_Raise; end Loggers;
with Ada.Text_IO; use Ada.Text_IO; with Loggers; use Loggers; procedure Show_No_Return_Exception is Check_Passed : constant Boolean := False; begin if not Check_Passed then Log_And_Raise ("Check failed!"); Put_Line ("This line will not be reached!"); end if; end Show_No_Return_Exception;

In this example, Log_And_Raise writes a message to the user and raises the Logged_Failure, so it never returns to the Show_No_Return_Exception procedure.

We could implement exception handling in the Show_No_Return_Exception procedure, so that the Logged_Failure exception could be handled there after it's raised in Log_And_Raise. However, this wouldn't be considered a normal return to the procedure because it wouldn't return to the point where it should (i.e. to the point where Put_Line is about to be called, right after the call to the Log_And_Raise procedure).

If a nonreturning procedure returns nevertheless, this is considered a program error, so that the Program_Error exception is raised. For example:

    
    
    
        
package Loggers is Logged_Failure : exception; procedure Log_And_Raise (Msg : String) with No_Return; end Loggers;
with Ada.Text_IO; use Ada.Text_IO; package body Loggers is procedure Log_And_Raise (Msg : String) is begin Put_Line (Msg); end Log_And_Raise; end Loggers;
with Ada.Text_IO; use Ada.Text_IO; with Loggers; use Loggers; procedure Show_No_Return_Exception is Check_Passed : constant Boolean := False; begin if not Check_Passed then Log_And_Raise ("Check failed!"); Put_Line ("This line will not be reached!"); end if; end Show_No_Return_Exception;

Here, Program_Error is raised when Log_And_Raise returns to the Show_No_Return_Exception procedure.

In the Ada Reference Manual

Inline subprograms

Inlining refers to a kind of optimization where the code of a subprogram is expanded at the point of the call in place of the call itself.

In modern compilers, inlining depends on the optimization level selected by the user. For example, if we select the higher optimization level, the compiler will perform automatic inlining agressively.

In the GNAT toolchain

The highest optimization level (-O3) of GNAT performs aggressive automatic inlining. This could mean that this level inlines too much rather than not enough. As a result, the cache may become an issue and the overall performance may be worse than the one we would achieve by compiling the same code with optimization level 2 (-O2). Therefore, the general recommendation is to not just select -O3 for the optimized version of an application, but instead compare it the optimized version built with -O2.

It's important to highlight that the inlining we're referring above happens automatically, so the decision about which subprogram is inlined depends entirely on the compiler. However, in some cases, it's better to reduce the optimization level and perform manual inlining instead of automatic inlining. We do that by using the Inline aspect.

Let's look at this example:

    
    
    
        
package Float_Arrays is type Float_Array is array (Positive range <>) of Float; function Average (Data : Float_Array) return Float with Inline; end Float_Arrays;
package body Float_Arrays is function Average (Data : Float_Array) return Float is Total : Float := 0.0; begin for Value of Data loop Total := Total + Value; end loop; return Total / Float (Data'Length); end Average; end Float_Arrays;
with Ada.Text_IO; use Ada.Text_IO; with Float_Arrays; use Float_Arrays; procedure Compute_Average is Values : constant Float_Array := (10.0, 11.0, 12.0, 13.0); Average_Value : Float; begin Average_Value := Average (Values); Put_Line ("Average = " & Float'Image (Average_Value)); end Compute_Average;

When compiling this example, the compiler will most probably inline Average in the Compute_Average procedure. Note, however, that the Inline aspect is just a recommendation to the compiler. Sometimes, the compiler might not be able to follow this recommendation, so it won't inline the subprogram.

These are some examples of situations where the compiler might not be able to inline a subprogram:

  • when the code is too large,

  • when it's too complicated — for example, when it involves exception handling —, or

  • when it contains tasks, etc.

In the GNAT toolchain

In order to effectively use the Inline aspect, we need to set the optimization level to at least -O1 and use the -gnatn switch, which instructs the compiler to take the Inline aspect into account.

In addition to the Inline aspect, in GNAT, we also have the (implementation-defined) Inline_Always aspect. In contrast to the former aspect, however, the Inline_Always aspect isn't primarily related to performance. Instead, it should be used when the functionality would be incorrect if inlining was not performed by the compiler. Examples of this are procedures that insert Assembly instructions that only make sense when the procedure is inlined, such as memory barriers.

Similar to the Inline aspect, there might be situations where a subprogram has the Inline_Always aspect, but the compiler is unable to inline it. In this case, we get a compilation error from GNAT.

Note that we can use the Inline aspect for generic subprograms as well. When we do this, we indicate to the compiler that we wish it inlines all instances of that generic subprogram.

In the Ada Reference Manual

Null Procedures

Null procedures are procedures that don't have any effect, as their body is empty. We declare a null procedure by simply writing is null in its declaration. For example:

    
    
    
        
package Null_Procs is procedure Do_Nothing (Msg : String) is null; end Null_Procs;

As expected, calling a null procedure doesn't have any effect. For example:

    
    
    
        
with Null_Procs; use Null_Procs; procedure Show_Null_Proc is begin Do_Nothing ("Hello"); end Show_Null_Proc;

Null procedures are equivalent to implementing a procedure with a body that only contains null. Therefore, the Do_Nothing procedure above is equivalent to this:

    
    
    
        
package Null_Procs is procedure Do_Nothing (Msg : String); end Null_Procs;
package body Null_Procs is procedure Do_Nothing (Msg : String) is begin null; end Do_Nothing; end Null_Procs;

Null procedures and overriding

We can use null procedures as a way to simulate interfaces for non-tagged types — similar to what actual interfaces do for tagged types. For example, we may start by declaring a type and null procedures that operate on that type. For example, let's model a very simple API:

    
    
    
        
package Simple_Storage is type Storage_Model is null record; procedure Set (S : in out Storage_Model; V : String) is null; procedure Display (S : Storage_Model) is null; end Simple_Storage;

Here, the API of the Storage_Model type consists of the Set and Display procedures. Naturally, we can use objects of the Storage_Model type in an application, but this won't have any effect:

    
    
    
        
with Ada.Text_IO; use Ada.Text_IO; with Simple_Storage; use Simple_Storage; procedure Show_Null_Proc is S : Storage_Model; begin Put_Line ("Setting 24..."); Set (S, "24"); Display (S); end Show_Null_Proc;

By itself, the Storage_Model type is not very useful. However, we can derive other types from it and override the null procedures. Let's say we want to implement the Integer_Storage type to store an integer value:

    
    
    
        
package Simple_Storage is type Storage_Model is null record; procedure Set (S : in out Storage_Model; V : String) is null; procedure Display (S : Storage_Model) is null; type Integer_Storage is private; procedure Set (S : in out Integer_Storage; V : String); procedure Display (S : Integer_Storage); private type Integer_Storage is record V : Integer := 0; end record; end Simple_Storage;
with Ada.Text_IO; use Ada.Text_IO; package body Simple_Storage is procedure Set (S : in out Integer_Storage; V : String) is begin S.V := Integer'Value (V); end Set; procedure Display (S : Integer_Storage) is begin Put_Line ("Value: " & S.V'Image); end Display; end Simple_Storage;
with Ada.Text_IO; use Ada.Text_IO; with Simple_Storage; use Simple_Storage; procedure Show_Null_Proc is S : Integer_Storage; begin Put_Line ("Setting 24..."); Set (S, "24"); Display (S); end Show_Null_Proc;

In this example, we can view Storage_Model as a sort of interface for derived non-tagged types, while the derived types — such as Integer_Storage — provide the actual implementation.

The section on null records contains an extended example that makes use of null procedures.

In the Ada Reference Manual