up

Introduction to Ada

 

Introduction

For a briefer introduction to a smaller subset of Ada, but with more explanation, see Robert Dewar's A Briefest Introduction to Ada 95. For the full language definition, see the Ada 95 Reference Manual. For other references and tutorials, see the Ada reference page.

Brief History


Review the waterfall model of software development, as the DoD applied it to the design of a language Here the "implementation" result was a programming language definition (book), not an implementation.

Problems: Insufficient prototyping and trial use to iron out bugs in specification. Several years delay in producing adequate compilers.

Advantage: very good requirements analysis. Probably the first time it was done for a programming language. Up 'til then (and probably still today) language design was an art, in which the personality of the designer(s) determined what went into the language. Other languages today (C++, Java, etc.) can still learn from the Ada requirements analysis.

Design principles of Ada

Ada, C++ and Java


Java and C++ have dominated Ada, mainly for non-technical reasons. However, ideas from Ada have been adopted by these languages as they evolved. During this evolution Java, originally promoted as small and simple, has grown huge. All these languages continue to get larger.

Ada goals

The canonical example

with Ada.Text_IO; use Ada.Text_IO;
procedure Hello is
begin
  Put_Line ("hello!");
end Hello;

A small package

package Math_Functions is
   function Sqrt (X : Float) return Float;
   function Exp (Base : Float; Exponent : Float) return Float;
end Math_Functions;

Using the package

with Ada.Text_IO; use Ada.Text_IO;
with Ada.Float_Text_IO; use Ada.Float_Text_IO;
with Math_Functions;
procedure Example2 is
   Val : Float;
begin
   Get (Val);
   Put ("Sqrt ("); Put (Val); Put (")=");
   Put (Math_Functions.Sqrt (Val));
   New_Line;
end Example2;

Implementing the package

package body Math_Functions is
   Epsilon : constant := 1.0e-6;
   function Sqrt (X : Float) return Float is
      Result : Float := X / 2.0;
   begin
      while abs (Result * Result - X) > Epsilon loop
         Result := 0.5 * (X / Result + Result);
      end loop;
      return Result;
   end Sqrt;
   ...
end Math_Functions;

Abstraction at its best: enumeration types

   type suit is (hearts, diamonds, spades, clubs);
   type direction is (east, west, north, south, lost);

Contrast C: "arithmetics on enum members may produce results in the underlying representation type that do not correspond to any declared enum number; this is not an error"

#include <stdio.h>
enum suit { hearts, diamonds, spades, clubs };
enum direction { east, west, north, south, lost };
int main () {
  enum suit X;
  int I = east + west;
  X = east;
  X = X + west;
  if (X != west) 
     printf ("X = %d\n", X);
     return I;
}

The above compiles and runs without any error messages. In contrast, consider the following attempt at writing the equivalent in Ada (which is not allowed):

with Ada.Text_IO; use Ada.Text_IO;
procedure Enums is
  type Suit is (Hearts, Diamonds, Spades, Clubs);
  type Direction is (East, West, North, South, Lost);
  X : Suit;
  I : Integer := east + west;
begin
  X := East;
  X := X + West;
  if X /= West then
     Put_Line (Integer'Image (Integer (X)));
  end if;
end Enums;
gcc -c enums.adb
enums.adb:6:23: invalid operand types for operator "+"
enums.adb:6:23: left operand has type "Direction" defined at line 4
enums.adb:6:23: right operand has type "Direction" defined at line 4
enums.adb:8:08: expected type "Suit" defined at line 3
enums.adb:8:08: found type "Direction" defined at line 4
enums.adb:9:10: invalid operand types for operator "+"
enums.adb:9:10: left operand has type "Suit" defined at line 3
enums.adb:9:10: right operand has type "Direction" defined at line 4
enums.adb:10:08: invalid operand types for operator "/="
enums.adb:10:08: left operand has type "Suit" defined at line 3
enums.adb:10:08: right operand has type "Direction" defined at line 4
enums.adb:11:40: illegal operand for numeric conversion
gnatmake: "enums.adb" compilation error

Iteration over an Enumeration Range

with Ada.Text_IO; use Ada.Text_IO;
procedure Enums2 is
  type Direction is (East, West, North, South, Lost);
begin
   for X in Direction loop
      Put (" " & Direction'Image (X) & " " & 
           Integer'Image (Direction'Pos (X)));
   end loop;
   New_Line;
end Enums2;

output:

 EAST  0 WEST  1 NORTH  2 SOUTH  3 LOST  4

C++ ended up adopting a more Ada-like model for enums. This is better in catching inconsistent usages, but it implicitly converts an enumeration value as an integer. This implicit conversion is less verbose than the Ada 'Pos function, but more prone to error. It seems that C++ has no equivalent to 'Succ (successor function) so it is not clear how to do a for-loop over a C++ enumeration without converting to type int.

Until recently, Java felt short of C++ with respect to enumeration types. The best that could be done was the following.

  static final int hearts = 0;
  static final int diamonds = 1;
  static final int spades = 2;
  static final int clubs = 3;

  static final int east = 0;
  static final int west = 1;
  static final int north = 2;
  static final int south = 3;
  static final int lost = 4;

This works like C, but doesn't have a type name to distinguish suits from directions. In Java 5, it seems there is a new extension:

public enum Suit { hearts, diamonds, spades, clubs }

Last time I tried this with gcj it did not recognize this syntax.

Enumeration types and strong typing

   type Fruit is (Apple, Orange, Grape, Apricot);
   type Vendor is (Apple, IBM, HP, Lenovo);
   My_PC : Vendor;
   Dessert : Fruit;
...
  My_PC := Apple;
  Dessert := Apple;
  Dessert := My_PC; --  ERROR

Built-in enumeration types

type Boolean is (False, True);

type Character is ( -- full ASCII (Ada 83) or ISO Latin_1 (Ada 95) );

type WideCharacter is ( -- Unicode, or ISO 646 );

Numeric types and strong typing

   type Day_of_Month is new Integer range 1 .. 31;
   type Day_of_Year is new Integer range 1 .. 366;
   Day1 : Day_Of_Month;
   Day2 : Day_Of_Year;
...
   Day1 := Day2; --  ERROR

Each of the above types is a distinct copy of the predefined type Integer. They have the same set of arithmetic operations, but values of the one type may not be mixed with values of the other type. This permits a compiler to catch accidental errors such as the one above.

Array types

Index types of an array type are typed:

type weekday is (Mon, Tue, Wed, Thu, Fri);
type workhours is array (Weekday) of Integer;
type pressure is array (1..1000, 1..1000, 1..1000) of Long_Float;

Prefefined array type:

type String is array (Positive range <>) of Character;

Record Types

type Buffer is record
  size : Positive;
  contents : String (1 .. 100);
end record;

B1 : Buffer;   -- can use B1, B1.size, B1.contents (1) ...

Access Types

type Handle is access Buffer;

Ptr : Handle := new Buffer;

The Ada language allows for automatic storage storage reclamation (garbage collection), but most (maybe all?) Ada implementations do it. Most Ada users are not willing to pay the price (in execution time and storage overhead) for this feature, and generally want to be in control of when storage is allocated and deallocated. Among high-integrity software developers there is a fear of storage leakage due to incomplete garbage collections, and of storage exhaustion through fragmentation caused by repeated dynamic allocation and deallocation. Among real-time developers there is also fear of missed deadlines due to long pauses while garbage collection is performed.

Therefore, the Ada culture is to try to avoid dynamic storage allocation, using static (global) and stack allocation wherever possible. When using dynamic storage allocation is necessary, one tries to design so that dynamically allocated objects are reused explicitly for objects of the same size and type.

If one must use dynamic deallocation, one can define ones own storage manager, or use an usafe interface called Unchecked_Deallocation, which is similar to the C/C++ "free" operations. The syntax for this, like all unsafe features, is intentionally cumbersome.

One can also implement one's own reference-count base storage reclamation using controlled types, as shown further below.

To use pointers with global and stack allocated objects one needs to use a special kind of access type, declared with access all, and special attributes 'Access and 'Unchecked_Access.

Ada Abstraction Mechanisms

Packages

A package for stacks

package Stacks is
   type Stack is private;
   procedure Push (Item : Character; On : in out Stack);
   procedure Pop (Item : Character; From : in out Stack);
   function is_Empty (S : Stack) return Boolean;
private
  type Stack is record
     top : Integer := 0;
     Contents : String (1 .. 80) := (others => '*');
  end record;
end Stacks;

This is just one part of the package declaration, the package specification (i.e., the interface).

Object-oriented programming

Type Extension

type Point is tagged record
   X_Coord, Y_Coord : Integer;
end record;

type Pixel is new Point with record
   R, G, B : Integer;
end record;

Inheritance

Polymorphism

Generic Units

A generic package

generic
   type T is private;
package Gstacks is
   type Stack is private;
   procedure Push (Item : T; On : in out Stack);
   procedure Pop (Item : T; From : in out Stack);
   function is_Empty (S : Stack) return Boolean;
private
  type Arr is array (1 .. 100) of T;
  type Stack is record
     top : Integer := 0;
     Contents : Arr;
  end record;
end Gstacks;

This is just the specification (interface) of the generic unit. It needs a body (implementation) to be complete.

A generic subprogram

generic
   type T is private;
   type Arr is array (Integer range <>) of T;
   with function "<" (X, Y : T) return Boolean;
procedure Gsort (Table : in out Arr);

Once again, this is just the specification (interface) of the generic unit. It needs a body (implementation) to be complete.

The type model

Types and subtypes

Strong typing: compile-time versus run-time checks

Built-in subtypes

type Integer is ... --  implementation defined

subtype Positive is Integer range 1 .. Integer'Last;  -- useful attribute
subtype Natural  is Integer range 0 .. Integer'Last;

X : Integer := 500;
Y : Positive := 2 * X;
Z : Natural := -Y;      --  legal, but raises Constraint_Error

Declarations and Scope

Blocks

declare
   X : Integer := F(5);
   Y : Integer := 2 * X;
   Z : Integer := Y * Z;     --  ERROR : premature
   X : Float;                --  ERROR : duplicate 
begin
   declare
      X : Float := Float (Y);  --  hides outer X
   begin
      Put_Line (Float'Image (X));
   end;
end;

How Ada declaration scopes work: Two-part model

    procedure
 1|    ... declarations only ...
  |   X : Integer;
    begin
  |     ... statements only ...
  |     ... outer declaration of X is in scope here ...
  |     declare 
  | 1|     ... declarations only ...
 2|  |    X : Integer;
  |    begin
  | 2|    ... statements only ...
  |  |    ... inner declaration of X hides outer one here ... 
  |  | end; 
  |    ... outer declaration of X is back in scope ...
    end;

Variables and Constants

Variable declaration:

   Limit : Integer := 25;
   Offset : Integer range 1 .. 20;

Constant declaration:

   Sqrt2 : constant Float := Sqrt (2.0);  --  not static
   Always : constant Boolean := True;   --  static value
   Never : constant Boolean := not Always  -- static expression

Ada distinguishes the quality of being static (value known at compile time) from being constant (not changing, once initialized).

Variables must be constrained

subtype is constrained:

First_Name : String (1 .. 5) := "Ralph";

but not necessarily static:

Last_Name : String (1 .. X * 2);

else subtype specification is indefinite but initial value provides constraint:

Comment : String := "this is obvious"; --  bounds are 1..15

Ada requires that the storage size of a variable object be fixed at the time the object is elaborated. This is described in terms of a constraint on the type of the object.

Multiple declarations

This, That : T := F (1, 2, 3);

is equivalent to

This : T := F (1, 2, 3);
That : T := F (1, 2, 3);

F is called twice. This is important if the expression has a side-effect:

type Ptr is access R;
P1, P2 : Ptr := new R;

causes two R's to be allocated

Number declarations

Pi : constant := 3.14159265;   -- type deduced from value
Half_Pi : constant := Pi / 2;  -- mixed arithmetic OK here, since static
Big : constant := 2 ** 200;    -- legal
One : constant := 2 * Big / (Big + Big)  -- must be exact

This is a rather noteworthy feature of Ada. Literal numbers are of "universal" types, that can be implicitly converted to any numeric type. Since the type to which they may need to be converted are not known in advance, the compiler cannot lose any precision in the computation of such values.

Scalar types

Integer types

Integer operations

comparison operators
addition operators
unary operators
multiplying operators
highest precedence operators
      =, /=, <, <=, >, >=
+
, -
+
, -
*
, /, mod, rem
**
, abs

Why Ada does not have a "++" Operator


See "The Development of the C Language", by Dennis Ritchie. The "++" operator was invented by Thompson, probably inspired by a feature of the PDP-7, which had a few "auto-increment" memory cells, with the property that an indirect memory reference through them incremented the cell. Besides conciseness, this notation allowed a simple compiler to recognize and optimize the increment operation. It worked well with the next generation (PDP-11) architecture, which had auto-increment and auto-decrement address modes.

The Ada designers chose not to have an increment and decrement operator, because of an aversion to side-effects in operators. The prevailing view was that expression should compute a value, without side-effects. That is also reflected in the restriction that functions cannot have "out" or "in out" parameters.

Boolean operations

The following are in addition to all the attributes of discrete types:

comparison operators
binary operators
unary operators
short-circuit operators
membership operators
      and, or, xor
not
and then, or else
in, not in

When in doubt, parenthesize!


This is good advice in most languages. Since precedence rules vary between languages, it is easy to get confused when reading or writing code with operators. It may seem ugly to add parentheses, but ugly is better than erroneous.

Attributes

Attributes of discrete types

Byte'First, Long_Integer'Last
Weekday'Succ (Today)
Integer'Succ (X * Y)
Boolean'Pred (True)
Boolean'Succ (True)
Weekday'Pos (Mon)
Weekday'Val (3)
Positive'Max (X, Y)
      -- applies to type or subtype
-- like function call
-- like adding one
-- yields False
-- raises an exception
-- yields 0
-- yields Thu
-- function with two arguments

Real Types

all computations are approximate:

fixed point type: absolute bound on error:

   type Temp is delta 2**(-16) range -100.0 .. 100.0;

floating point type: relative bound on error:

   type Angle is digits 7 range -2.0 .. 2.0;

predefined floating point types: Float, Long_Float, etc.

Derived Types

general mechanism for creating new types with the properties of existing types

   type Like_T is new T;  --  same set of values, same operations, but not mixable
   type Small_Int is range 1 .. 10;

is equivalent to

   type Anon is new Integer;
   type Small_Int is Anon range 1 .. 10;

and all arithmetic operations are inherited

Array types

index types can be any discrete type

component type must be definite (so of uniform size)

   type Class_List is array (1 .. 100) of String (1 .. 10);  -- OK
   type Class_List is array (1 .. 100) of String;  -- ERROR

subtype constrains all indices or none:

   type Matrix is array
      (positive range <>, positive range <>) of Long_Float;
   subtype Table is Matrix;
   subtype Rotation is Matrix (1 .. 3, 1 .. 3);

Anonymous array types

   Grades : array (1.. Num_Students) of Natural;

type of Grades has no name, is distinct from any other array type

   Ar1, Ar2 : array (1 .. 10) of Boolean;
   ...
   Ar1 := Ar2;   --  ERROR : different (anonymous) types

If a type is useful, it deserves to have a name.

Array attributes

type Matrix is array (Positive range <>, Positive range <>) of Float;
subtype Rect is Matrix (1 .. 3, 1 .. 5);
M3 : Rect;
M3'First (1)                         --  yields 1
M3'First                             --  same
Rect'Length (2)                      --  yields 5 (applies to type)
M3'Range (2)                         --  equivalent to 1 .. 5
String'Length                        --  ERRR : String is unconstrained

Array aggregates

expression yields an array value:

   A := (1, 2, 3, 10);              --  positional
   A := (1, others => 0);           --  notation for default
   A := (1..3 => 1, 4 => -999);    --  component associations

default can only be used if bounds are known:

   A : String (1 .. 10) := (others => '?');  -- OK
        A : String := (others => '?');   --  ERROR : unknown bounds

Compiler must check that every element of A is covered. In the above case A must have index range 1..5.

Ada philosophy of error detection and handling: Any operation that fails should do so explictly, in a way that forces the programmer to pay attention, rather than quietly continuing execution. Compare the Ada failure of a file open operation (raises an exception) with the C way of signalling failure (return -1), and the Ada way of indicating failure of storage allocation (raises an exception) with the C way of indicating (malloc returns null).

Strings


As we move down the list, we pay a higher price in performance to achieve greater flexibility. Going from fixed-size allocation to variable-sized allocation, we risk greater external storage fragmentation, which makes the memory manager work harder. In return, we get the ability to have My_String objects of different sizes, and reduce internal fragmentation. Going from direct allocation in one record to storing the string in a separate location, we gain the ability to dynamically vary the length of a My_String object, but we double the number of storage allocations, making the storage manager work still harder, and we probably reduce cache performance, since the My_String object and the string object will be in different cache lines.

Ada has a standard implementation of the third approach, in package Ada.Strings.Unbounded. The unbounded string package allows us to concatenate strings of different lengths, and dynamically adjusts the size to fit. For example:

S : Unbounded_String;
C : Character;
...
S := S & C;

The latter would not be legal if S were of type String, but it is OK for type Unbounded_String. The concatenation operator does the extra work of allocating new storage.

Aggregates and qualification

aggregate may be ambiguous

   type Vector is array (1 .. 3) of Float;
   procedure Display (V : Vector);
   type Assay is array (1 .. 3) of Float;
   procedure Display (A : Assay);
   ...
   Display ((1.0, 1.2, 1.5));          --  ERROR : ambiguous
   Display (Vector'(1.0, 1.2, 1.5));   --  OK

Multidimensional arrays

aggregates are given in row-major order with subaggregates:

   type Square is array (1 .. 3, 1 .. 3) of Integer;
   Unit : constant Square := ((1, 0, 0), (0, 1, 0), (0, 0, 1));

a two-dimensional array is NOT the same as an array of arrays:

   type Vector is array (1 .. 3) of Integer;
   type V3 is array (1 .. 3) of Vector;  --  not convertible to Square

Ada identifiers and reserved words are case-insensitive. For example "Integer", "INTEGER", "integer", and "InTeGeR" all mean the same thing. Why do you think this rule was adopted by the language designer?

Operations on one dimensional arrays

Boolean operations extend pointwise:

   type Set is array (1 .. Card) of Boolean;
   S1, S2, S3 : Set;
   ...
   S3 := S1 and S2;  --  intersection

so do lexicographic comparisons on arrays of discrete types:

   S1 := (T, T, T);
   S2 := (T, T, F);
   ... S2 < S1       --  yields True

Concatenation and slicing

Both operations yield the base type:

   type Table is array (1 .. 10) of Integer;
   T1, T2 : Table;

What type is "T1 & T2"? How about "T1(X .. Y)"?

Declaration equivalent to:

   type Anon is array (Integer range <>) of Integer;
   subtype Table is Anon (1 .. 10);

So "T1 & T2" and "T1 (X .. Y)" are of an anonymous type unconstrained array type

Specifying a range

subtype Sub is Positive range 2 .. 4;
Label : String (1 .. 10) := "transcends";
...
  Label (2 .. 4)                --  yields "ran"
  Label (Integer range 2 .. 4)  -- same
  Label (Sub)                   -- same

Ranges also used in loops and case statements

Control structures

Conventional sequential constructs

+ more novel forms for task communication

If statement

If Done (X, Y) then
   Success;
   Close_Up;
elsif Almost_Done (X) then  --  the only keyword that isn't English
   Hurry (Y);
else
   if X = 0 then Call_For_Help (X); else Panic; end if;
end if;

Loops

infinite loop:

   loop
      Put_Line ("Forever");
   end loop;

in general, better to stop:

   loop
       Put_Line ("Still going");
       exit when Time_Is_Up;  -- must yield Boolean value
   end loop;

Loops over discrete ranges

for J in 1 .. 1000 loop ...           --  declares J

for K in 1 .. 0 loop ...              --  empty range

for Month in Feb .. Nov loop ...
for Month in Months range Feb .. Nov loop ...

for K in Positive loop ...            --  might take a long time

for Num in reverse 1 .. 1000 loop ... --  descending order

While loops

   while abs (Result * Result - X) > Epsilon loop
      Result := 0.5 * (X / Result + Result);
   end loop;

effect of until can be obtained with exit statement

Named loop

search : 
   while X > 0 loop
      X := F (X, Y);
refine :
      for J in 1 .. N loop
         Y := G (Z);
         exit search when X = 0.0;
      end loop refine;
      if T > 20 then exit; end if;    -- alternate form
   end loop search;

Case statements

Case statements


Contrast with C switch statements:

Goto statement


Certain kinds of gotos are not permitted, including jumps into a loop or a branch of an if-statement.

Can you think of situations in which using a goto statement is arguably better than using the built-in control structures?

Exception handling

with Ada.Text_IO; use Ada.Text_IO;
procedure Exceptions is
   E : exception;
   procedure Q is
   begin raise E;
   end Q;
   procedure P is
   begin Q;
   exception
      when E => Put_Line ("caught E in P"); raise;
   end P;
begin P;
exception when E => Put_Line ("caught E in main procedure");
   when others => null;
end Exceptions;

Output is:

caught E in P
caught E in main procedure

Exceptions propagate to handlers.

Exception handler is potential third part of any block

    procedure
  |    ... declarations only ...
1 |   X : Integer;
  |    ... exceptions raised here are propagated outward
    begin
  |    ... statements only ...
2 |    ... exceptions raised here are handled in (3) below
  |
    exception
  |    when My_Exception =>  
3 |       ... recovery statements ...
  |       ... exceptions raised here are propagated outward
  |    when others =>  
  |       ... recovery statements ...
    end;

More elaborate exception handling

with Ada.Exceptions; use Ada.Exceptions;
...
exception
   when E =>
      Put_Line ("caught E in P");
      raise Program_Error;
   when X : others =>
      Put_Line ("caught " & Exception_Name (X) & "P");
end P;

See also explanation of Ada exceptions as compared to C++ and Java exceptions in notes on exception handling.

Concurrent control structures


We will look at these in more detail if we get around to talking about concurrent programming.

Subprograms

Functions

function F (X : Integer := 0;
            Y : Float := Pi;
            Maybe : Boolean := True)
return Integer;
...
F (10, 0.0, False)
F (5)                 --  equivalent to F (5, Pi, True)
F (Maybe => False)    --  equivalent to F (), Pi, False)

Operators

like functions, but usable in infix notatation

package Bignums is
   type Bignum is private;
   Zero : constant Bignum;
   function "+" (X, Y : Bignum) return Bignum;
   function "*" (X, Y : Bignum) return Bignum;
   function Image (X, Y : Bignum) return String;
private ...
end Bignums;

must respect syntax: no defaults, no unary "*", etc.

Procedures

like functions, but do not return a value

procedure Swap (A, B : in out Integer) is
   T : Integer := A;
begin
   A := B; B := T;
end Swap;

Controlled Types and Pointers: Example of Use

with Ada.Strings.Maps;
with Ada.Finalization;
package Ada.Strings.Unbounded is
pragma Preelaborate (Unbounded);

   type Unbounded_String is private;
   Null_Unbounded_String : constant Unbounded_String;
   ...
   procedure Free (X : in out String_Access);
   ...
   function "&"
     (Left  : in Unbounded_String;
      Right : in Character)
      return  Unbounded_String;
   ...
   function "&"
     (Left  : Unbounded_String;
      Right : String)
     return  Unbounded_String;
   ...
private
   ...
   package AF renames Ada.Finalization;
   ...
   type Unbounded_String is new AF.Controlled with record
      Reference : String_Access := Null_String'Access;
   end record;
   ...
   pragma Finalize_Storage_Only (Unbounded_String);
   --  allows compiler to omit Finalize call for library-level objects
   procedure Initialize (Object : in out Unbounded_String);
   procedure Adjust     (Object : in out Unbounded_String);
   procedure Finalize   (Object : in out Unbounded_String);
   ...
   Null_Unbounded_String : constant Unbounded_String :=
     (AF.Controlled with Reference => Null_String'Access);
   
end Ada.Strings.Unbounded;

The type Ada.Finalization.Controlled is used to implement unbounded strings. This tagged type and all types derived from it are called controlled types. Controlled types provide a basis for user-definable storage management, through appropriate redefinition of the inherited operations "initialize", "finalize", and "adjust". The compiler generates (hidden) calls to these operations at appropriate points.

It is instructive to read the full specification of this package. First, look in the reference manual; then look at the implementation-dependent parts in the Gnat runtime library; finally, read the body.

Take note of the overriding of the inherited declarations of the Initialize, Adjust, and Finalize operations of the tagged type Unbounded_String.

Also take note of the special form of aggregate for Null_Unbounded_String, to handle the type extension.

Concatenation Operation

Two of several implementations of the concatenation operator, overloaded for various combinations of argument types:

function "&"
  (Left  : Unbounded_String;
   Right : Character)
   return  Unbounded_String
is 
   Length : constant Integer := Left.Reference.all'Length + 1;
   Result : Unbounded_String;

begin
   Result.Reference := new String (1 .. Length);
   Result.Reference.all (1 .. Length - 1) := Left.Reference.all;
   Result.Reference.all (Length)          := Right;
   return Result;
end "&";
function "&"
  (Left  : Unbounded_String;
   Right : String)
   return  Unbounded_String
is
   L_Length : constant Integer := Left.Reference.all'Length;
   Length   : constant Integer := L_Length +  Right'Length;
   Result   : Unbounded_String;

begin
   Result.Reference := new String (1 .. Length);
   Result.Reference.all (1 .. L_Length)          := Left.Reference.all;
   Result.Reference.all (L_Length + 1 .. Length) := Right;
   return Result;
end "&";

Notice that this convenience of expression (using unbounded strings and concatenation) incurs quite a bit of overhead, due to the new allocation and the copying. In an assignment like S := S & 'c'; there will also be a call to the adjust routine

Consider the assembly language code produced by gcc for the following.

with Ada.Strings.Unbounded; use Ada.Strings.Unbounded;
with Ada.Text_IO; use Ada.Text_IO;
procedure TestCat is
   S : Unbounded_String := To_Unbounded_String ("ab");
begin
   S := S & 'c';
   Put_Line (To_String (S));
end TestCat;

You will see that a lot of the code has to do with exception handling and finalization. That is to make certain the storage for S is recovered on return from the subprogram TestCat. Can you find the code for the assignment statement? Look for the call to the adjust routine.

Compare this against the assembly language code for the following.

with Ada.Text_IO; use Ada.Text_IO;
procedure TestCat0 is
   S : String (1 .. 3) := "ab ";
begin
   S(3) := 'c';
   Put_Line (S);
end TestCat0;

To see that the amount of overhead for using unbounded dynamic strings is not Ada-specific, compare the assembly language code for the following C++ program.

using namespace std;
#include <iostream>
#include <string>
int main() {
  string S("ab");
  S = S + 'c';
  cout << S << endl;
}

All examples were compiled with the "-O2" option on the gcc compiler. Note that the C++ verison is actually longer, even though it is not include the code provided by the Ada compiler to make the initialization and finalization safe against asynchronous thread cancelation (task abort, in Ada terminology).

Free

called explicitly by the *user* to free an object:

procedure Free (X : in out String_Access) is
   procedure Deallocate is
      new Ada.Unchecked_Deallocation (String, String_Access);
begin
   --  Note: Don't try to free statically allocated null string
   if X /= Null_Unbounded_String.Reference then
      Deallocate (X);
   end if;
end Free;

Note the local instantiation of generic procedure Unchecked_Deallocation. This is analogous to C's free, but must be instantiated separately for each pair of (object_type, access_type), to satisfy Ada's strong typing rules.

Initialize

called implicitly (by the compiler) on object just after storage is allocated:

procedure Initialize (Object : in out Unbounded_String) is
begin
   Object.Reference := Null_Unbounded_String.Reference;
end Initialize;

This initializes the object to refer to the null string.

Finalize

called implicitly (by the compiler) on object just before storage is recovered:

procedure Finalize (Object : in out Unbounded_String) is
   procedure Deallocate is
      new Ada.Unchecked_Deallocation (String, String_Access);
begin
   --  Note: Don't try to free statically allocated null string
   if Object.Reference /= Null_String'Access then
      Deallocate (Object.Reference);
      Object.Reference := Null_Unbounded_String.Reference;
   end if;
end Finalize;

This resets the object to refer to the null string, after recovering the storage of the old object.

Adjust

called implicitly (by the compiler) on LHS object after bit-copy phase of assignment:

procedure Adjust (Object : in out Unbounded_String) is
begin
   --  Copy string, except we do not copy the statically allocated null
   --  string, since it can never be deallocated.
   if Object.Reference /= Null_String'Access then
      Object.Reference := new String'(Object.Reference.all);
   end if;
end Adjust;

The previous phase of assignment just called Finalize on the old value of the object (to recover the storage), then copied into it the new reference. The above code then called to allocate storage and replace the copied reference by a refernce to the new copy of the referenced object.

A few of the many features not covered above

Original used by permission of E. Schoenberg of New York University. Revised and extended by T. P. Baker 2005, 2007.
($Id: ada-intro.html,v 1.1 2005/09/02 13:18:59 baker Exp baker $)