Ada Programming/Object Orientation

From Wikibooks, open books for an open world
Jump to navigation Jump to search

Ada. Time-tested, safe and secure.
Ada. Time-tested, safe and secure.

Object orientation in Ada[edit | edit source]

Object oriented programming consists in building the software in terms of "objects". An "object" contains data and has a behavior. The data, normally, consists in constants and variables as seen in the rest of this book but could also, conceivably, reside outside the program entirely, i.e. on disk or on the network. The behavior consists in subprograms that operate on the data. What makes Object Orientation unique, compared to procedural programming, is not a single feature but the combination of several features:

  • encapsulation, i.e. the ability to separate the implementation of an object from its interface; this in turn separates "clients" of the object, who can only use the object in certain predefined ways, from the internals of the object, which have no knowledge of the outside clients.
  • inheritance, the ability for one type of objects to inherit the data and behavior (subprograms) of another, without necessarily needing to break encapsulation;
  • type extension, the ability for an object to add new data components and new subprograms on top of the inherited ones and to replace some inherited subprograms with its own versions; this is called overriding.
  • polymorphism, the ability for a "client" to use the services of an object without knowing the exact type of the object, i.e. in an abstract way. Indeed at run time, the actual objects can have different types from one invocation to the next.

It is possible to do object-oriented programming in any language, even assembly. However, type extension and polymorphism are very difficult to get right without language support.

In Ada, each of these concepts has a matching construct; this is why Ada supports object-oriented programming directly.

  • Packages provide encapsulation;
  • Derived types provide inheritance;
  • Record extensions, described below, provide for type extension;
  • Class-wide types, also described below, provide for polymorphism.

Ada has had encapsulation and derived types since the first version (MIL-STD-1815 in 1980), which led some to qualify the language as "object-oriented" in a very narrow sense. Record extensions and class-wide types were added in Ada 95. Ada 2005 further adds interfaces. The rest of this chapter covers these aspects.

The simplest object: the Singleton[edit | edit source]

package Directory is
  function Present (Name_Pattern: String) return Boolean;
  generic
     with procedure Visit (Full_Name, Phone_Number, Address: String;
                           Stop: out Boolean);
  procedure Iterate (Name_Pattern: String);
end Directory;

The Directory is an object consisting of data (the telephone numbers and addresses, presumably held in an external file or database) and behavior (it can look an entry up and traverse all the entries matching a Name_Pattern, calling Visit on each).

A simple package provides for encapsulation (the inner workings of the directory are hidden) and a pair of subprograms provide the behavior.

This pattern is appropriate when only one object of a certain type must exist; there is, therefore, no need for type extension or polymorphism.

Primitive operations[edit | edit source]

In Ada, methods are usually referred to by the technical term primitive subprograms of a tagged type or the equivalent term primitive operations of a tagged type. The primitive operations of a type are those that are always available wherever the type is used. For the tagged types that are used in object oriented programming, they also can be inherited by and overridden by derived types, and can be dynamically dispatched.

Primitive operations of a type need to be declared immediately within the same package as the type (not within a nested package nor a child package). For tagged types, new primitive operations and overrides of inherited primitive operations are further required to be declared before the freezing point of the type. Any subprograms declared after the freezing point will not be considered primitive, and therefore cannot be inherited and are not dynamically dispatched. Freezing points are discussed in more detail below, but the simple practice of declaring all primitive operations immediately following the initial type declaration will ensure that those subprograms are indeed recognized as primitive.

Primitive operations of type T need to have at least one parameter of type T or of type access T. While most object-oriented languages automatically provide a this or self pointer, Ada requires that you explicitly declare a formal parameter to receive the current object. That typically will be the first parameter in the list, which enables the object.subprogram call syntax (available since Ada 2005), but it may be at any parameter position. Tagged types are always passed by reference; the parameter passing method has nothing to do with the parameter modes in and out, which describe the dataflow. The parameter passing method is identical for T and access T.

For tagged types, no other directly dispatchable types can be used in the parameter list because Ada doesn't offer multiple dispatching. The following example is illegal.

package P is
   type A is tagged private;
   type B is tagged private;
   procedure Proc (This: B; That: A); -- illegal: can't dispatch on both A and B
end P;

When additional dispatchable objects need to be passed in, the parameter list should declare them using their class-wide types, T'Class. For example:

package P is
   type A is tagged private;
   type B is tagged private;
   procedure Proc (This: B; That: A'Class); -- dispatching only on B
end P;

Note, however, that this does not limit the number of parameters of the same tagged type. For example, the following definition is legal.

package P is
   type A is tagged private;
   procedure Proc (This, That: A); -- dispatching only on A
end P;

Primitive operations of tagged types are dispatching operations. Whether a call to such a primitive operation is in effect dispatching or statically bound, depends on the context (see below). Note that in a dispatching call both actual parameters of the last example must have the same tag (i.e. the same type); Constraint_Error will be called if the tag check fails.

Derived types[edit | edit source]

Type derivation has been part of Ada since the very start.

package P is
  type T is private;
  function Create (Data: Boolean) return T;  -- primitive
  procedure Work (Object : in out T);        -- primitive
  procedure Work (Pointer: access T);        -- primitive
  type Acc_T is access T;
  procedure Proc (Pointer: Acc_T);           -- not primitive
private
  type T is record
    Data: Boolean;
  end record;
end P;

The above example creates a type T that contains data (here just a Boolean but it could be anything) and behavior consisting of some subprograms. It also demonstrates encapsulation by placing the details of the type T in the private part of the package.

The primitive operations of T are the function Create, the overloaded procedures Work, and the predefined "=" operator; Proc is not primitive, since it has an access type on T as parameter — don't confuse this with an access parameter, as used in the second procedure Work. When deriving from T, the primitive operations are inherited.

with P;
package Q is
  type Derived is new P.T;
end Q;

The type Q.Derived has the same data and the same behavior as P.T; it inherits both the data and the subprograms. Thus it is possible to write:

with Q;
procedure Main is
  Object: Q.Derived := Q.Create (Data => False);
begin
  Q.Work (Object);
end Main;

Inherited operations may be overridden and new operations added, but the rules (Ada 83) unfortunaltely are somewhat different from the rules for tagged types (Ada 95).

Admittedly, the reasons for writing this may seem obscure. The purpose of this kind of code is to have objects of types P.T and Q.Derived, which are not compatible:

Ob1: P.T;
Ob2: Q.Derived;
Ob1 := Ob2;              -- illegal
Ob1 := P.T (Ob2);        -- but convertible
Ob2 := Q.Derived (Ob1);  -- in both directions

This feature is not used very often (it's used e.g. for declaring types reflecting physical dimensions) but I present it here to introduce the next step: type extension.

Type extensions[edit | edit source]

Type extensions are an Ada 95 amendment.

A tagged type provides support for dynamic polymorphism and type extension. A tagged type bears a hidden tag that identifies the type at run-time. Apart from the tag, a tagged record is like any other record, so it can contain arbitrary data.

package Person is
   type Object is tagged
     record
         Name   : String (1 .. 10);
         Gender : Gender_Type;
     end record;
   procedure Put (O : Object);
end Person;

As you can see, a Person.Object is an object in the sense that it has data and behavior (the procedure Put). However, this object does not hide its data; any program unit that has a with Person clause can read and write the data in a Person.Object directly. This breaks encapsulation and also illustrates that Ada completely separates the concepts of encapsulation and type. Here is a version of Person.Object that encapsulates its data:

package Person is
   type Object is tagged private;
   procedure Put (O : Object);
private
   type Object is tagged
     record
         Name   : String (1 .. 10);
         Gender : Gender_Type;
     end record;
end Person;

Because the type Person.Object is tagged, it is possible to create a record extension, which is a derived type with additional data.

with Person;
package Programmer is
   type Object is new Person.Object with private;
private
   type Object is new Person.Object with
     record
        Skilled_In : Language_List;
     end record;
end Programmer;

The type Programmer.Object inherits the data and behavior, i.e. the type's primitive operations, from Person.Object; it is thus possible to write:

with Programmer;
procedure Main is
   Me : Programmer.Object;
begin
   Programmer.Put (Me);
   Me.Put; -- equivalent to the above, Ada 2005 only
end Main;

So the declaration of the type Programmer.Object, as a record extension of Person.Object, implicitly declares a procedure Put that applies to a Programmer.Object.

Like in the case of untagged types, objects of type Person and Programmer are convertible. However, where untagged objects are convertible in either direction, conversion of tagged types only works in the direction to the root. (Conversion away from the root would have to add components out of the blue.) Such a conversion is called a view conversion, because components are not lost, they only become invisible.

Extension aggregates have to be used if you go away from the root.

Overriding[edit | edit source]

Now that we have introduced tagged types, record extensions and primitive operations, it becomes possible to understand overriding. In the examples above, we introduced a type Person.Object with a primitive operation called Put. Here is the body of the package:

with Ada.Text_IO;
package body Person is
   procedure Put (O : Object) is
   begin
      Ada.Text_IO.Put (O.Name);
      Ada.Text_IO.Put (" is a ");
      Ada.Text_IO.Put_Line (Gender_Type'Image (O.Gender));
   end Put;
end Person;

As you can see, this simple operation prints both data components of the record type to standard output. Now, remember that the record extension Programmer.Object has an additional data member. If we write:

with Programmer;
procedure Main is
   Me : Programmer.Object;
begin
   Programmer.Put (Me);
   Me.Put; -- equivalent to the above, Ada 2005 only
end Main;

then the program will call the inherited primitive operation Put, which will print the name and gender but not the additional data. In order to provide this extra behavior, we must override the inherited procedure Put like this:

with Person;
package Programmer is
   type Object is new Person.Object with private;
   overriding -- Optional keyword, new in Ada 2005
   procedure Put (O : Object);
private
   type Object is new Person.Object with
     record
        Skilled_In : Language_List;
     end record;
end Programmer;
package body Programmer is
   procedure Put (O : Object) is
   begin
      Person.Put (Person.Object (O)); -- view conversion to the ancestor type
      Put (O.Skilled_In); -- presumably declared in the same package as Language_List
   end Put;
end Programmer;

Programmer.Put overrides Person.Put; in other words it replaces it completely. Since the intent is to extend the behavior rather than replace it, Programmer.Put calls Person.Put as part of its behavior. It does this by converting its parameter from the type Programmer.Object to its ancestor type Person.Object. This construct is a view conversion; contrary to a normal type conversion, it does not create a new object and does not incur any run-time cost (and indeed, if the operand of such view conversion was actually a variable, the result can be used when an out parameter is required (eg. procedure call)). Of course, it is optional that an overriding operation call its ancestor; there are cases where the intent is indeed to replace, not extend, the inherited behavior.

(Note that also for untagged types, overriding of inherited operations is possible. The reason why it's discussed here is that derivation of untagged types is done rather seldom.)

Polymorphism, class-wide programming and dynamic dispatching[edit | edit source]

The full power of object orientation is realized by polymorphism, class-wide programming and dynamic dispatching, which are different words for the same, single concept. To explain this concept, let us extend the example from the previous sections, where we declared a base tagged type Person.Object with a primitive operation Put and a record extension Programmer.Object with additional data and an overriding primitive operation Put.

Now, let us imagine a collection of persons. In the collection, some of the persons are programmers. We want to traverse the collection and call Put on each person. When the person under consideration is a programmer, we want to call Programmer.Put; when the person is not a programmer, we want to call Person.Put. This, in essence, is polymorphism, class-wide programming and dynamic dispatching.

With Ada's strong typing, ordinary calls cannot be dynamically dispatched; a call to an operation on a declared type must always be statically bound to go to the operation defined for that specific type. Dynamic dispatching (known as simply dispatching in Ada parlance) is provided through separate class-wide types that are polymorphic. Each tagged type, such as Person.Object, has a corresponding class of types which is the set of types comprising the type Person.Object itself and all types that extend Person.Object. In our example, this class consists of two types:

  • Person.Object
  • Programmer.Object

Ada 95 defines the Person.Object'Class attribute to denote the corresponding class-wide type. In other words:

declare
   Someone : Person.Object'Class := ...; -- to be expanded later
begin
   Someone.Put; -- dynamic dispatching
end;

The declaration of Someone denotes an object that may be of either type, Person.Object or Programmer.Object. Consequently, the call to the primitive operation Put dispatches dynamically to either Person.Put or Programmer.Put.

The only problem is that, since we don't know whether Someone is a programmer or not, we don't know how many data components Someone has, either, and therefore we don't know how many bytes Someone takes in memory. For this reason, the class-wide type Person.Object'Class is indefinite. It is impossible to declare an object of this type without giving some constraint. It is, however, possible to:

  • declare an object of a class-wide with an initial value (as above). The object is then constrained by its initial value.
  • declare an access value to such an object (because the access value has a known size);
  • pass objects of a class-wide type as parameters to subprograms
  • assign an object of a specific type (in particular, the result of a function call) to a variable of a class-wide type.

With this knowledge, we can now build a polymorphic collection of persons; in this example we will quite simply create an array of access values to persons:

with Person;
procedure Main is
   type Person_Access is access Person.Object'Class;
   type Array_Of_Persons  is array (Positive range <>) of Person_Access;

   function Read_From_Disk return Array_Of_Persons is separate;

   Everyone : constant Array_Of_Persons := Read_From_Disk;
begin -- Main
   for K in Everyone'Range loop
      Everyone (K).all.Put; -- dereference followed by dynamic dispatching
   end loop;
end Main;

The above procedure achieves our desired goal: it traverses the array of Persons and calls the procedure Put that is appropriate for each person.

Advanced topic: How dynamic dispatching works[edit | edit source]

You don't need to know how dynamic dispatching works in order to use it effectively but, in case you are curious, here is an explanation.

The first component of each object in memory is the tag; this is why objects are of a tagged type rather than plain records. The tag really is an access value to a table; there is one table for each specific type. The table contains access values to each primitive operation of the type. In our example, since there are two types Person.Object and Programmer.Object, there are two tables, each containing a single access value. The table for Person.Object contains an access value to Person.Put and the table for Programmer.Object contains an access value to Programmer.Put. When you compile your program, the compiler constructs both tables and places them in the program executable code.

Each time the program creates a new object of a specific type, it automatically sets its tag to point to the appropriate table.

Each time the program performs a dispatching call of a primitive operation, the compiler inserts object code that:

  • dereferences the tag to find the table of primitive operations for the specific type of the object at hand
  • dereferences the access value to the primitive operation
  • calls the primitive operation.

Conversely, when the program performs a call where the parameter is a view conversion to an ancestor type, the compiler performs these two dereferences at compile time rather than run time: such a call is statically bound; the compiler emits code that directly calls the primitive operation of the ancestor type specified in the view conversion.

Redispatching[edit | edit source]

Dispatching is controlled by the (hidden) tag of the object. So what happens when a primitive operation Op1 calls another primitive operation Op2 on the same object?

 type Root is tagged private;
 procedure Op1 (This: Root);
 procedure Op2 (This: Root);

 type Derived is new Root with private;
 -- Derived inherits Op1
 overriding procedure Op2 (This: Derived);

 procedure Op1 (This: Root) is
 begin
   ...
   Op2 (This);               -- not redispatching
   Op2 (Root'Class (This));  -- redispatching
   This.Op2;                 -- not redispatching (new syntax since Ada 2005)
   (Root'Class (This)).Op2;  -- redispatching (new syntax since Ada 2005)
   ...
 end Op1;

 D: Derived;
 C: Root'Class := D;

 Op1 (D);  -- statically bound call
 Op1 (C);  -- dispatching call
 D.Op1;    -- statically bound call (new syntax since Ada 2005)
 C.Op1;    -- dispatching call (new syntax since Ada 2005)

In this fragment, Op1 is not overridden, whereas Op2 is overridden. The body of Op1 calls Op2, so which Op2 will be called if Op1 is called for an object of type Derived?

The basic rules of dispatching still apply. Calls to Op2 will be dispatched when called using an object of a class-wide type.

The formal parameter lists for the operations specify the type of This to be a specific type, not class-wide. In fact, that parameter must be a specific type so that the operation will be dispatched for objects of that type, and to allow the operation's code to access any additional data items associated with that type. If you want redispatching, you must state that explicitly by converting the parameter of the specific type to the class-wide type again. (Remember: view conversions never lose components, they just hide them. A conversion to a class-wide type can unhide them again.) The first call Op1 (D) (statically bound, i.e., not dispatching) executes the inherited Op1 — and within Op1, the first call to Op2 is also statically bound (there is no redispatching) because parameter This is a view conversion to specific type Root. However, the second call is dispatching because the parameter This is converted to the class-wide type. That call dispatches to the overriding Op2.

Because the conventional This.Op2 call is not dispatching, the call will be to Root.Op2 even though the object itself is of type Derived and the Op2 operation is overridden. This is very different from how other OO languages behave. In other OO languages, a method is either dispatching or not. In Ada, an operation is either available for dispatching or not. Whether or not dispatching is actually used for a given call depends on the way that the object's type is specified at that call point. For programmers accustomed to other OO languages, it can come as quite a surprise that calls from a dispatchable operation to other operations on the same object are, by default, not (dynamically) dispatched.

The default of not redispatching is not an issue if all of the operations have been overridden, because they all will be operating on the expected type of object. However, it has ramifications when writing code for types that might be extended by another type sometime in the future. It's possible that the new type will not work as intended if it doesn't override all of the primitive operations that call other primitive operations. The safest policy is to use a class-wide conversion of the object to force dispatching of calls. One way to accomplish that is to define a class-wide constant in each dispatched method:

 procedure Op2 (This: Derived) is
   This_Class: constant Root'Class := This;
 begin

This is needed to access data items and to make any non-dispatching calls. This_Class is needed to make dispatching calls.

Less commonly encountered and perhaps less surprising, calls from a non-dispatchable (class-wide) routine for a tagged type to other routines on the same object are, by default, dispatched:

 type Root is tagged private;
 procedure Op1 (This: Root'Class);
 procedure Op2 (This: Root);

 type Derived is new Root with private;
 -- Derived does not inherit Op1, rather Op1 is applicable to Derived.
 overriding procedure Op2 (This: Derived);

 procedure Op1 (This: Root'Class) is
 begin
   ...
   Op2 (This);               -- dispatching
   Op2 (Root (This));        -- static call
   This.Op2;                 -- dispatching (new syntax since Ada 2005)
   (Root (This)).Op2;        -- static call (new syntax since Ada 2005)
   ...
 end Op1;

 D: Derived;
 C: Root'Class := D;

 Op1 (D);  -- static call
 Op1 (C);  -- static call
 D.Op1;    -- static call (new syntax since Ada 2005)
 C.Op1;    -- static call (new syntax since Ada 2005)

Note that calls on Op1 are always static, since Op1 is not inherited. Its parameter type is class-wide, so the operation is applicable to all types derived from Root. (Op2 has an entry for each type derived from Root in the dispatch table. There is no such dispatch table for Op1; rather there is only one such operation for all types in the class.)

Normal calls from Op1 are dispatched because the declared type of This is class-wide. The default to dispatching usually isn't bothersome because class-wide operations are typically used to perform a script involving calls to one or more dispatched operations.

Run-time type identification[edit | edit source]

Run-time type identification allows the program to (indirectly or directly) query the tag of an object at run time to determine which type the object belongs to. This feature, obviously, makes sense only in the context of polymorphism and dynamic dispatching, so works only on tagged types.

You can determine whether an object belongs to a certain class of types, or to a specific type, by means of the membership test in, like this:

type Base    is tagged private;
type Derived is new Base    with private;
type Leaf    is new Derived with private;

...
procedure Explicit_Dispatch (This : in Base'Class) is
begin
   if This in Leaf then ... end if;
   if This in Derived'Class then ... end if;
end Explicit_Dispatch;

Thanks to the strong typing rules of Ada, run-time type identification is in fact rarely needed; the distinction between class-wide and specific types usually allows the programmer to ensure objects are of the appropriate type without resorting to this feature.

Additionally, the reference manual defines package Ada.Tags (RM 3.9(6/2)), attribute 'Tag (RM 3.9(16,18)), and function Ada.Tags.Generic_Dispatching_Constructor (RM 3.9(18.2/2)), which enable direct manipulation with tags.

Creating Objects[edit | edit source]

The Language Reference Manual's section on 3.3: Objects and Named Numbers [Annotated] states when an object is created, and destroyed again. This subsection illustrates how objects are created.

The LRM section starts,

Objects are created at run time and contain a value of a given type. An object can be created and initialized as part of elaborating a declaration, evaluating an allocator, aggregate, or function_call.

For example, assume a typical hierarchy of object oriented types: a top-level type Person, a Programmer type derived from Person, and possibly more kinds of persons. Each person has a name; assume Person objects to have a Name component. Likewise, each Person has a Gender component. The Programmer type inherits the components and the operations of the Person type, so Programmer objects have a Name and a Gender component, too. Programmer objects may have additional components specific to programmers.

Objects of a tagged type are created the same way as objects of any type. The second LRM sentence says, for example, that an object will be created when you declare a variable or a constant of a type. For the tagged type Person,

declare
   P: Person;
begin
   Text_IO.Put_Line("The name is " & P.Name);
end;

Nothing special so far. Just like any ordinary variable declaration this O-O one is elaborated. The result of elaboration is an object named P of type Person. However, P has only default name and gender value components. These are likely not useful ones. One way of giving initial values to the object's components is to assign an aggregate.

declare
   P: Person := (Name => "Scorsese", Gender => Male);
begin
   Text_IO.Put_Line("The name is " & P.Name);
end;

The parenthesized expression after := is called an aggregate (4.3: Aggregates [Annotated]).

Another way to create an object that is mentioned in the LRM paragraph is to call a function. An object will be created as the return value of a function call. Therefore, instead of using an aggregate of initial values, we might call a function returning an object.

Introducing proper O-O information hiding, we change the package containing the Person type so that Person becomes a private type. To enable clients of the package to construct Person objects we declare a function that returns them. (The function may do some interesting construction work on the objects. For instance, the aggregate above will most probably raise the exception Constraint_Error depending on the name string supplied; the function can mangle the name so that it matches the declaration of the component.) We also declare a function that returns the name of Person objects.

package Persons is

   type Person is tagged private;

   function Make (Name: String; Sex: Gender_Type) return Person;

   function Name (P: Person) return String;

private
   type Person is tagged
      record
         Name   : String (1 .. 10);
         Gender : Gender_Type;
      end record;

end Persons;

Calling the Make function results in an object which can be used for initialization. Since the Person type is private we can no longer refer to the Name component of P. But there is a corresponding function Name declared with type Person making it a socalled primitive operation. (The component and the function in this example are both named Name However, we can choose a different name for either if we want.)

declare
   P: Person := Make (Name => "Orwell", Sex => Male);
begin
   Text_IO.Put_Line("The name is " & Name(P));
end;

Objects can be copied into another. The target object is first destroyed. Then the component values of the source object are assigned to the corresponding components of the target object. In the following example, the default initialized P gets a copy of one of the objects created by the Make calls.

declare
   P: Person;
begin
   if 2001 > 1984 then
      P := Make (Name => "Kubrick", Sex => Male);
   else
      P := Make (Name => "Orwell", Sex => Male);
   end if;

   Text_IO.Put_Line("The name is " & Name(P));
end;

So far, there is no mention of the Programmer type derived from Person. There is no polymorphism yet, and likewise initialization does not yet mention inheritance. Before dealing with Programmer objects and their initialization a few words about class-wide types are in order.

More details on primitive operations[edit | edit source]

Remember what we said before about "Primitive Operations". Primitive operations are:

  • subprograms taking a parameter of the tagged type;
  • functions returning an object of the tagged type;
  • subprograms taking a parameter of an anonymous access type to the tagged type;
  • In Ada 2005 only, functions returning an anonymous access type to the tagged type;

Additionally, primitive operations must be declared before the type is frozen (the concept of freezing will be explained later):

Examples:

package X is
   type Object is tagged null record;

   procedure Primitive_1 (This : in     Object);
   procedure Primitive_2 (That :    out Object);
   procedure Primitive_3 (Me   : in out Object);
   procedure Primitive_4 (Them : access Object);
   function  Primitive_5 return Object;
   function  Primitive_6 (Everyone : Boolean) return access Object;
end X;

All of these subprograms are primitive operations.

A primitive operation can also take parameters of the same or other types; also, the controlling operand does not have to be the first parameter:

package X is
   type Object is tagged null record;

   procedure Primitive_1 (This : in Object; Number : in Integer);
   procedure Primitive_2 (You  : in Boolean; That : out Object);
   procedure Primitive_3 (Me, Her : in out Object);
end X;

The definition of primitive operations specifically excludes named access types and class-wide types as well as operations not defined immediately in the same declarative region. Counter-examples:

package X is
   type Object is tagged null record;
   type Object_Access is access Object;
   type Object_Class_Access is access Object'Class;

   procedure Not_Primitive_1 (This : in     Object'Class);
   procedure Not_Primitive_2 (This : in out Object_Access);
   procedure Not_Primitive_3 (This :    out Object_Class_Access);
   function  Not_Primitive_4 return Object'Class;

   package Inner is
       procedure Not_Primitive_5 (This : in Object);
   end Inner;
end X;

Advanced topic: Freezing rules[edit | edit source]

Freezing rules (ARM 13.14) are perhaps the most complex part of the Ada language definition; this is because the standard tries to describe freezing as unambiguously as possible. Also, that part of the language definition deals with freezing of all entities, including complicated situations like generics and objects reached by dereferencing access values. You can, however, get an intuitive understanding of freezing of tagged types if you understand how dynamic dispatching works. In that section, we saw that the compiler emits a table of primitive operations for each tagged type. The point in the program text where this happens is the point where the tagged type is frozen, i.e. the point where the table becomes complete. After the type is frozen, no more primitive operations can be added to it.

This point is the earliest of:

  • the end of the package spec where the tagged type is declared
  • the appearance of the first type derived from the tagged type

Example:

package X is

  type Object is tagged null record;
  procedure Primitive_1 (This: in Object);

  -- this declaration freezes Object
  type Derived is new Object with null record;

  -- illegal: declared after Object is frozen
  procedure Primitive_2 (This: in Object);

end X;

Intuitively: at the point where Derived is declared, the compiler starts a new table of primitive operations for the derived type. This new table, initially, is equal to the table of the primitive operations of the parent type, Object. Hence, Object must freeze.

  • the declaration of a variable of the tagged type

Example:

package X is

  type Object is tagged null record;
  procedure Primitive_1 (This: in Object);

  V: Object;  -- this declaration freezes Object

  -- illegal: Primitive operation declared after Object is frozen
  procedure Primitive_2 (This: in Object);

end X;

Intuitively: after the declaration of V, it is possible to call any of the primitive operations of the type on V. Therefore, the list of primitive operations must be known and complete, i.e. frozen.

  • The completion (not the declaration, if any) of a constant of the tagged type:
package X is

  type Object is tagged null record;
  procedure Primitive_1 (This: in Object);

  -- this declaration does NOT freeze Object
  Deferred_Constant: constant Object;

  procedure Primitive_2 (This : in Object); -- OK

private

  -- only the completion freezes Object
  Deferred_Constant: constant Object := (null record);

  -- illegal: declared after Object is frozen
  procedure Primitive_3 (This: in Object);

 end X;

New features of Ada 2005[edit | edit source]

This language feature is only available from Ada 2005 on.

Ada 2005 adds overriding indicators, allows anonymous access types in more places and offers the object.method notation.

Overriding indicators[edit | edit source]

The new keyword overriding can be used to indicate whether an operation overrides an inherited subprogram or not. Its use is optional because of upward-compatibility with Ada 95. For example:

package X is
    type Object is tagged null record;

   function  Primitive return access Object; -- new in Ada 2005

   type Derived_Object is new Object with null record;

   not overriding -- new optional keywords in Ada 2005
   procedure Primitive (This : in Derived_Object); -- new primitive operation

   overriding
   function  Primitive return access Derived_Object;
end X;

The compiler will check the desired behaviour.

This is a good programming practice because it avoids some nasty bugs like not overriding an inherited subprogram because the programmer spelt the identifier incorrectly, or because a new parameter is added later in the parent type.

It can also be used with abstract operations, with renamings, or when instantiating a generic subprogram:

not overriding
procedure Primitive_X (This : in Object) is abstract;

overriding
function  Primitive_Y return Object renames Some_Other_Subprogram;

not overriding
procedure Primitive_Z (This : out Object)
      is new Generic_Procedure (Element => Integer);

Object.Method notation[edit | edit source]

We have already seen this notation:

package X is
   type Object is tagged null record;

   procedure Primitive (This: in Object; That: in Boolean);
end X;
with X;
procedure Main is
   Obj : X.Object;
begin
   Obj.Primitive (That => True); -- Ada 2005 object.method notation
end Main;

This notation is only available for primitive operations where the controlling parameter is the first parameter.

Abstract types[edit | edit source]

A tagged type can also be abstract (and thus can have abstract operations):

package X is

   type Object is abstract tagged …;

   procedure One_Class_Member      (This : in     Object);
   procedure Another_Class_Member  (This : in out Object);
   function  Abstract_Class_Member return Object  is abstract;

end X;

An abstract operation cannot have any body, so derived types are forced to override it (unless those derived types are also abstract). See next section about interfaces for more information about this.

The difference with a non-abstract tagged type is that you cannot declare any variable of this type. However, you can declare an access to it, and use it as a parameter of a class-wide operation.

Multiple Inheritance via Interfaces[edit | edit source]

This language feature is only available from Ada 2005 on.

Interfaces allow for a limited form of multiple inheritance (taken from Java). On a semantic level they are similar to an "abstract tagged null record" as they may have primitive operations but cannot hold any data and thus these operations cannot have a body, they are either declared abstract or null. Abstract means the operation has to be overridden, null means the default implementation is a null body, i.e. one that does nothing.

An interface is declared with:

package Printable is
   type Object is interface;
   procedure Class_Member_1 (This : in     Object) is abstract;
   procedure Class_Member_2 (This :    out Object) is null;
end Printable;

You implement an interface by adding it to a concrete class:

with Person;
package Programmer is
   type Object is new Person.Object
                  and Printable.Object
   with
      record
         Skilled_In : Language_List;
      end record;
   overriding
   procedure Class_Member_1   (This : in Object);
   not overriding
   procedure New_Class_Member (This : Object; That : String);
end Programmer;

As usual, all inherited abstract operations must be overridden although null subprograms ones need not.

Such a type may implement a list of interfaces (called the progenitors), but can have only one parent. The parent may be a concrete type or also an interface.

type Derived is new Parent and Progenitor_1 and Progenitor_2 ... with ...;

Multiple Inheritance via Mix-in[edit | edit source]

Ada supports multiple inheritance of interfaces (see above), but only single inheritance of implementation. This means that a tagged type can implement multiple interfaces but can only extend a single ancestor tagged type.

This can be problematic if you want to add behavior to a type that already extends another type; for example, suppose you have

type Base is tagged private;
type Derived is new Base with private;

and you want to make Derived controlled, i.e. add the behavior that Derived controls its initialization, assignment and finalization. Alas you cannot write:

type Derived is new Base and Ada.Finalization.Controlled with private; -- illegal

since Ada.Finalization for historical reasons does not define interfaces Controlled and Limited_Controlled, but abstract types.

If your base type is not limited, there is no good solution for this; you have to go back to the root of the class and make it controlled. (The reason will become obvious presently.)

For limited types however, another solutions is the use of a mix-in:

type Base is tagged limited private;
type Derived;

type Controlled_Mix_In (Enclosing: access Derived) is
  new Ada.Finalization.Limited_Controlled with null record;

overriding procedure Initialize (This: in out Controlled_Mix_In);
overriding procedure Finalize   (This: in out Controlled_Mix_In);

type Derived is new Base with record
  Mix_In: Controlled_Mix_In (Enclosing => Derived'Access); -- special syntax here
  -- other components here...
end record;

This special kind of mix-in is an object with an access discriminant that references its enclosing object (also known as Rosen trick). In the declaration of the Derived type, we initialize this discriminant with a special syntax: Derived'Access really refers to an access value to the current instance of type Derived. Thus the access discriminant allows the mix-in to see its enclosing object and all its components; therefore it can initialize and finalize its enclosing object:

overriding procedure Initialize (This: in out Controlled_Mix_In) is
  Enclosing: Derived renames This.Enclosing.all;
begin
  -- initialize Enclosing...
end Initialize;

and similarly for Finalize.

The reason why this does not work for non-limited types is the self-referentiality via the discriminant. Imagine you have two variables of such a non-limited type and assign one to the other:

X := Y;

In an assignment statement, Adjust is called only after Finalize of the target X and so cannot provide the new value of the discriminant. Thus X.Mixin_In.Enclosing will inevitably reference Y.

Now let's further extend our hierarchy:

type Further is new Derived with null record;

overriding procedure Initialize (This: in out Further);
overriding procedure Finalize   (This: in out Further);

Oops, this does not work because there are no corresponding procedures for Derived, yet – so let's quickly add them.

type Base is tagged limited private;
type Derived;

type Controlled_Mix_In (Enclosing: access Derived) is
  new Ada.Finalization.Limited_Controlled with null record;

overriding procedure Initialize (This: in out Controlled_Mix_In);
overriding procedure Finalize   (This: in out Controlled_Mix_In);

type Derived is new Base with record
  Mix_In: Controlled_Mix_In (Enclosing => Derived'Access);  -- special syntax here
  -- other components here...
end record;

not overriding procedure Initialize (This: in out Derived);  -- sic, they are new
not overriding procedure Finalize   (This: in out Derived);

type Further is new Derived with null record;
overriding procedure Initialize (This: in out Further);
overriding procedure Finalize   (This: in out Further);

We have of course to write not overriding for the procedures on Derived because there is indeed nothing they could override. The bodies are

not overriding procedure Initialize (This: in out Derived) is
begin
  -- initialize Derived...
end Initialize;
overriding procedure Initialize (This: in out Controlled_Mix_In) is
  Enclosing: Derived renames This.Enclosing.all;
begin
  Initialize (Enclosing);
end Initialize;

To our dismay, we have to learn that Initialize/Finalize for objects of type Further will not be called, instead those for the parent Derived. Why?

declare
  X: Further;  -- Initialize (Derived (X)) is called here
begin
  null;
end;  -- Finalize (Derived (X)) is called here

The reason is that the mix-in defines the local object Enclosing to be of type Derived in the renames-statement above. To cure this, we have necessarily to use the dreaded redispatch (shown in different but equivalent notations):

overriding procedure Initialize (This: in out Controlled_Mix_In) is
  Enclosing: Derived renames This.Enclosing.all;
begin
  Initialize (Derived'Class (Enclosing));
end Initialize;
overriding procedure Finalize (This: in out Controlled_Mix_In) is
  Enclosing: Derived'Class renames Derived'Class (This.Enclosing.all);
begin
  Enclosing.Finalize;
end Finalize;
declare
  X: Further;  -- Initialize (X) is called here
begin
  null;
end;  -- Finalize (X) is called here

Alternatively (and presumably better still) is to write

type Controlled_Mix_In (Enclosing: access Derived'Class) is
  new Ada.Finalization.Limited_Controlled with null record;

Then we automatically get redispatch and can omit the type conversions on Enclosing.

Class names[edit | edit source]

Both the class package and the class record need a name. In theory they may have the same name, but in practice this leads to nasty (because of unintuitive error messages) name clashes when you use the use clause. So over time three de facto naming standards have been commonly used.

Classes/Class[edit | edit source]

The package is named by a plural noun and the record is named by the corresponding singular form.

package Persons is

   type Person is tagged
      record
         Name   : String (1 .. 10);
         Gender : Gender_Type;
      end record;

end Persons;

This convention is the usually used in Ada's built-in libraries.

Disadvantage: Some "multiples" are tricky to spell, especially for those of us who aren't native English speakers.

Class/Object[edit | edit source]

The package is named after the class, the record is just named Object.

package Person is

   type Object is tagged
      record
         Name   : String (1 .. 10);
         Gender : Gender_Type;
      end record;

end Person;

Most UML and IDL code generators use this technique.

Disadvantage: You can't use the use clause on more than one such class packages at any one time. However you can always use the "type" instead of the package.

Class/Class_Type[edit | edit source]

The package is named after the class, the record is postfixed with _Type.

package Person is

   type Person_Type is tagged
      record
         Name   : String (1 .. 10);
         Gender : Gender_Type;
      end record;

end Person;

Disadvantage: lots of ugly "_Type" postfixes.

Object-Oriented Ada for C++ programmers[edit | edit source]

In C++, the construct

 struct C {
   virtual void v();
   void w();
   static void u();
 };

is strictly equivalent to the following in Ada:

package P is
  type C is tagged null record;
  procedure V (This : in out C);        -- primitive operation, will be inherited upon derivation
  procedure W (This : in out C'Class);  -- not primitive, will not be inherited upon derivation
  procedure U;
end P;

In C++, member functions implicitly take a parameter this which is of type C*. In Ada, all parameters are explicit. As a consequence, the fact that u() does not take a parameter is implicit in C++ but explicit in Ada.

In C++, this is a pointer. In Ada, the explicit This parameter does not have to be a pointer; all parameters of a tagged type are implicitly passed by reference anyway.

Static dispatching[edit | edit source]

In C++, function calls dispatch statically in the following cases:

  • the target of the call is an object type
  • the member function is non-virtual

For example:

 C object;
 object.v();
 object.w();

both dispatch statically. In particular, the static dispatch for v() may be confusing; this is because object is neither a pointer nor a reference. Ada behaves exactly the same in this respect, except that Ada calls this static binding rather than dispatching:

declare
   Object : P.C;
begin
   Object.V; -- statically bound
   Object.W; -- statically bound
end;

Dynamic dispatching[edit | edit source]

In C++, a function call dispatches dynamically if the two following conditions are met simultaneously:

  • the target of the call is a pointer or a reference
  • the member function is virtual.

For example:

 C* object;
 object->v(); // dynamic dispatch
 object->w(); // static, non-virtual member function
 object->u(); // illegal: static member function
 C::u(); // static dispatch

In Ada, a primitive subprogram call dispatches (dynamically) if and only if:

  • the target object is of a class-wide type;

Note: In Ada vernacular, the term dispatching always means dynamic.

For example:

declare
   Object : P.C'Class := ...;
begin
   P.V (Object); -- dispatching
   P.W (Object); -- statically bound: not a primitive operation
   P.U; -- statically bound
end;

As can be seen there is no need for access types or pointers to do dispatching in Ada. In Ada, tagged types are always passed by-reference to subprograms without the need for explicit access values.

Also note that in C++, the class serves as:

  • the unit of encapsulation (Ada uses packages and visibility for this)
  • the type, like in Ada.

As a consequence, you call C::u() in C++ because u() is encapsulated in C, but P.U in Ada since U is encapsulated in the package P, not the type C.

Class-wide and specific types[edit | edit source]

The most confusing part for C++ programmers is the concept of a "class-wide type". To help you understand:

  • pointers and references in C++ are really, implicitly, class-wide;
  • object types in C++ are really specific;
  • C++ provides no way to declare the equivalent of:
type C_Specific_Access is access C;
  • C++ provides no way to declare the equivalent of:
type C_Specific_Access_One is access C;
type C_Specific_Access_Two is access C;

which, in Ada, are two different, incompatible types, possibly allocating their memory from different storage pools!

  • In Ada, you do not need access values for dynamic dispatching.
  • In Ada, you use access values for dynamic memory management (only) and class-wide types for dynamic dispatching (only).
  • In C++, you use pointers and references both for dynamic memory management and for dynamic dispatching.
  • In Ada, class-wide types are explicit (with 'Class).
  • In C++, class-wide types are implicit (with * or &).

Constructors[edit | edit source]

in C++, a special syntax declares a constructor:

 class C {
    C(/* optional parameters */); // constructor
 };

A constructor cannot be virtual. A class can have as many constructors, differentiated by their parameters, as necessary.

Ada does not have such constructors. Perhaps they were not deemed necessary since in Ada, any function that returns an object of the tagged type can serve as a kind of constructor. This is however not the same as a real constructor like the C++ one; this difference is most striking in cases of derivation trees (see Finalization below). The Ada constructor subprograms do not have to have a special name and there can be as many constructors as necessary; each function can take parameters as appropriate.

package P is
  type T is tagged private;
  function Make                 return T;  -- constructor
  function To_T (From: Integer) return T;  -- another constructor
  procedure Make (This: out T);            -- not a constructor
private
  ...
end P;

If an Ada constructor function is also a primitive operation (as in the example above), it becomes abstract upon derivation and has to be overridden if the derived type is not itself abstract. If you do not want this, declare such functions in a nested scope.

In C++, one idiom is the copy constructor and its cousin the assignment operator:

 class C {
    C(const C& that); // copies "that" into "this"
    C& operator= (const C& right); // assigns "right" to "this", which is "left"
 };

This copy constructor is invoked implicitly on initialization, e.g.

 C a = b; // calls the copy constructor
 C c;
 a = c;   // calls the assignment operator

Ada provides a similar functionality by means of controlled types. A controlled type is one that extends the predefined type Ada.Finalization.Controlled:

with Ada.Finalization;
package P is
  type T is new Ada.Finalization.Controlled with private;
  function Make return T;  -- constructor
private
  type T is ... end record;
  overriding procedure Initialize (This: in out T);
  overriding procedure Adjust     (This: in out T); -- copy constructor
end P;

Note that Initialize is not a constructor; it resembles the C++ constructor in some way, but is also very different. Suppose you have a type T1 derived from T with an appropriate overriding of Initialize. A real constructor (like the C++ one) would automatically first construct the parent components (T), then the child components. In Ada, this is not automatic. In order to mimic this in Ada, we have to write:

procedure Initialize (This: in out T1) is
begin
  Initialize (T (This));  -- Don't forget this part!
  ...  -- handle the new components here
end Initialize;

The compiler inserts a call to Initialize after each object of type T is allocated when no initial value is given. It also inserts a call to Adjust after each assignment to the object. Thus, the declarations:

A: T;
B: T := X;

will:

  • allocate memory for A
  • call Initialize (A)
  • allocate memory for B
  • copy the contents of X to B
  • call Adjust (B)

Initialize (B) will not be called because of the explicit initialization.

So, the equivalent of a copy constructor is an overriding of Adjust.

If you would like to provide this functionality to a type that extends another, non-controlled type, see "Multiple Inheritance".

Destructors[edit | edit source]

In C++, a destructor is a member function with only the implicit this parameter:

 class C {
    virtual ~C(); // destructor
 }

While a constructor cannot be virtual, a destructor must be virtual if the class is to be used with dynamic dispatch (has virtual methods or derives from a class with virtual methods). C++ classes do not use dynamic dispatch by default, so it can catch some programmers out and wreak havoc in their programs by simply forgetting the keyword virtual.

In Ada, the equivalent functionality is again provided by controlled types, by overriding the procedure Finalize:

with Ada.Finalization;
package P is
   type T is new Ada.Finalization.Controlled with private;
   function Make return T;  -- constructor
private
   type T is ... end record;
   overriding procedure Finalize (This: in out T);  -- destructor
end P;

Because Finalize is a primitive operation, it is automatically "virtual"; you cannot, in Ada, forget to make a destructor virtual.

Encapsulation: public, private and protected members[edit | edit source]

In C++, the unit of encapsulation is the class; in Ada, the unit of encapsulation is the package. This has consequences on how an Ada programmer places the various components of an object type.

 class C {
 public:
    int a;
    void public_proc();
 protected:
    int b;
    int protected_func();
 private:
    bool c;
    void private_proc();
 };

A way to mimic this C++ class in Ada is to define a hierarchy of types, where the base type is the public part, which must be abstract so that no stand-alone objects of this base type can be defined. It looks like so:

private with Ada.Finalization;

package CPP is

  type Public_Part is abstract tagged record  -- no objects of this type
    A: Integer;
  end record;

  procedure Public_Proc (This: in out Public_Part);

  type Complete_Type is new Public_Part with private;

  -- procedure Public_Proc (This: in out Complete_Type);  -- inherited, implicitly defined

private  -- visible for children

  type Private_Part;  -- declaration stub
  type Private_Part_Pointer is access Private_Part;

  type Private_Component is new Ada.Finalization.Controlled with record
    P: Private_Part_Pointer;
  end record;

  overriding procedure Initialize (X: in out Private_Component);
  overriding procedure Adjust     (X: in out Private_Component);
  overriding procedure Finalize   (X: in out Private_Component);

  type Complete_Type is new Public_Part with record
    B: Integer;
    P: Private_Component;  -- must be controlled to avoid storage leaks
  end record;

  not overriding procedure Protected_Proc (This: Complete_Type);

end CPP;

The private part is defined as a stub only, its completion is hidden in the body. In order to make it a component of the complete type, we have to use a pointer since the size of the component is still unknown (the size of a pointer is known to the compiler). With pointers, unfortunately, we incur the danger of memory leaks, so we have to make the private component controlled.

For a little test, this is the body, where the subprogram bodies are provided with identifying prints:

with Ada.Unchecked_Deallocation;
with Ada.Text_IO;

package body CPP is

  procedure Public_Proc (This: in out Public_Part) is  -- primitive
  begin
    Ada.Text_IO.Put_Line ("Public_Proc" & Integer'Image (This.A));
  end Public_Proc;

  type Private_Part is record  -- complete declaration
    C: Boolean;
  end record;

  overriding procedure Initialize (X: in out Private_Component) is
  begin
    X.P := new Private_Part'(C => True);
    Ada.Text_IO.Put_Line ("Initialize " & Boolean'Image (X.P.C));
  end Initialize;

  overriding procedure Adjust (X: in out Private_Component) is
  begin
    Ada.Text_IO.Put_Line ("Adjust " & Boolean'Image (X.P.C));
    X.P := new Private_Part'(C => X.P.C);  -- deep copy
  end Adjust;

  overriding procedure Finalize (X: in out Private_Component) is
    procedure Free is new Ada.Unchecked_Deallocation (Private_Part, Private_Part_Pointer);
  begin
    Ada.Text_IO.Put_Line ("Finalize " & Boolean'Image (X.P.C));
    Free (X.P);
  end Finalize;

  procedure Private_Proc (This: in out Complete_Type) is  -- not primitive
  begin
    Ada.Text_IO.Put_Line ("Private_Proc" & Integer'Image (This.A) & Integer'Image (This.B) & ' ' & Boolean'Image (This.P.P.C));
  end Private_Proc;

  not overriding procedure Protected_Proc (This: Complete_Type) is  -- primitive
    X: Complete_Type := This;
  begin
    Ada.Text_IO.Put_Line ("Protected_Proc" & Integer'Image (This.A) & Integer'Image (This.B));
    Private_Proc (X);
  end Protected_Proc;

end CPP;

We see that, due to the construction, the private procedure is not a primitive operation.

Let's define a child class so that the protected operation can be reached:

package CPP.Child is
 
  procedure Do_It (X: Complete_Type);  -- not primitive

end CPP.Child;

A child can look inside the private part of the parent and thus can see the protected procedure:

with Ada.Text_IO;

package body CPP.Child is

  procedure Do_It (X: Complete_Type) is
  begin
    Ada.Text_IO.Put_Line ("Do_It" & Integer'Image (X.A) & Integer'Image (X.B));
    Protected_Proc (X);
  end Do_It;

end CPP.Child;

This is a simple test program, its output is shown below.

with CPP.Child;
use  CPP.Child, CPP;

procedure Test_CPP is

  X, Y: Complete_Type;

begin

  X.A := +1;
  Y.A := -1;

  Public_Proc (X);  Do_It (X);
  Public_Proc (Y);  Do_It (Y);

  X := Y;

  Public_Proc (X);  Do_It (X);

end Test_CPP;

This is the commented output of the test program:

Initialize TRUE                     Test_CPP: Initialize X
Initialize TRUE                                      and Y
Public_Proc 1                       |  Public_Proc (X):  A=1
Do_It 1-1073746208                  |  Do_It (X):        B uninitialized
Adjust TRUE                         |  |  Protected_Proc (X): Adjust local copy X of This
Protected_Proc 1-1073746208         |  |  |
Private_Proc 1-1073746208 TRUE      |  |  |  Private_Proc on local copy of This
Finalize TRUE                       |  |  Protected_Proc (X): Finalize local copy X
Public_Proc-1                       |  ditto for Y
Do_It-1 65536                       |  |
Adjust TRUE                         |  |
Protected_Proc-1 65536              |  |
Private_Proc-1 65536 TRUE           |  |
Finalize TRUE                       |  |
Finalize TRUE                       |  Assignment: Finalize target X.P.C
Adjust TRUE                         |  |           Adjust: deep copy
Public_Proc-1                       |  again for X, i.e. copy of Y
Do_It-1 65536                       |  |
Adjust TRUE                         |  |
Protected_Proc-1 65536              |  |
Private_Proc-1 65536 TRUE           |  |
Finalize TRUE                       |  |
Finalize TRUE                       Finalize Y
Finalize TRUE                            and X

You see that a direct translation of the C++ behaviour into Ada is difficult, if feasible at all. Methinks, the primitive Ada subprograms corresponds more to virtual C++ methods (in the example, they are not). Each language has its own idiosyncrasies which have to be taken into account, so that attempts to directly translate code from one into the other may not be the best approach.

De-encapsulation: friends and stream input-output[edit | edit source]

In C++, a friend function or class can see all members of the class it is a friend of. Friends break encapsulation and are therefore to be discouraged. In Ada, since packages and not classes are the unit of encapsulation, a "friend" subprogram is simply one that is declared in the same package as the tagged type.

In C++, stream input and output are the particular case where friends are usually necessary:

 #include <iostream>
 class C {
 public:
    C();
    friend ostream& operator<<(ostream& output, C& arg);
 private:
    int a, b;
    bool c;
 };

 #include <iostream>
 int main() {
    C object;
    cout << object;
    return 0;
 };

Ada does not need this construct because it defines stream input and output operations by default: The default implementation of the Input, Output, Read and Write attributes may be overridden (shown for Write as an example). The overriding must occur before the type is frozen, i.e. (in the case of this example) in the package specification.

private with Ada.Streams;  -- needed only in the private part
package P is
   type C is tagged private;
private
   type C is tagged record
      A, B : Integer;
      C : Boolean;
   end record;
   procedure My_Write (Stream : not null access Ada.Streams.Root_Stream_Type'Class;
                       Item   : in C);
   for C'Write use My_Write;  -- override the default attribute
end P;

By default, the Write attribute sends the components to the stream in the same order as given in the declaration, i.e. A, B then C, so we change the order.

package body P is
   procedure My_Write (Stream : not null access Ada.Streams.Root_Stream_Type'Class;
                       Item : in C) is
   begin
      -- The default implementation is to write A then B then C; here we change the order.
      Boolean'Write (Stream, Item.C);  -- call the
      Integer'Write (Stream, Item.B);  --   default attributes
      Integer'Write (Stream, Item.A);  --      for the components
   end My_Write;
end P;

Now P.C'Write calls the overridden version of the package.

 with Ada.Text_IO.Text_Streams;
 with P;
 procedure Main is
    Object : P.C;
 begin
    P.C'Write (Ada.Text_IO.Text_Streams.Stream (Ada.Text_IO.Standard_Output),
               Object);
 end Main;

Note that the stream IO attributes are not primitive operations of the tagged type; this is also the case in C++ where the friend operators are not, in fact, member functions of the type.

Terminology[edit | edit source]

Ada C++
Package class (as a unit of encapsulation)
Tagged type class (of objects) (as a type) (not pointer or reference, which are class-wide)
Primitive operation virtual member function
Tag pointer to the virtual table
Class (of types) a tree of classes, rooted by a base class and including all the (recursively-)derived classes of that base class
Class-wide type -
Class-wide operation static member function
Access value to a specific tagged type -
Access value to a class-wide type pointer or reference to a class

See also[edit | edit source]

Wikibook[edit | edit source]

Wikipedia[edit | edit source]

Ada Reference Manual[edit | edit source]

Ada 95[edit | edit source]

Ada 2005[edit | edit source]

Ada Quality and Style Guide[edit | edit source]