Introduction

So the C programming language has been getting a lot of bad press recently; a really stupid bug in some C code has compromised some of the core security infrastructure on the internet. The fix is easy, but the knock-on effects are going to go on for years and will cost serious amounts of money. As a result, people have been asking: why are we still writing software in a language which makes writing secure, robust code so hard?

It's a fair question. We've known that C is a bad language for years. No bounds checking, a module system that's enough to make grown adults weep, a notoriously difficult-to-parse syntax, a type system which is more of a set of guidelines than anything else, a whole bunch of historical idiocies like requiring forward declarations, and so much undefined behaviour that actually writing a well-defined program is something only the experts can do...

The answer, of course, is that we've been using C because it's everywhere, and everyone knows it, and everything interfaces to it. Because it compiles down to raw machine code with practically no runtime requirements it's got very low overhead, either performance-wise or conceptually. It's ubiquitous because it's the lowest common denominator, not because it's technically superior.

So, why aren't there any other languages with the same advantages but which are also real programming languages with proper abstractions underpinning them?

There are, of course, and recently I've been reading up on one of the originals: Ada. Here is a short, incomplete random walk through the language.

About Ada

Ada is a Wirth-family programming language designed by the US Department of Defence for robust embedded systems. The first version came out in 1980, but there have been periodic updates and there's still work being done on the language today --- the most recent update was Ada 2012.

It compiles into real machine code. On amd64, with gnat (the standard open source Ada compiler), a function which adds two numbers and returns the result compiles into precisely two instructions, one of which is ret.

You can have garbage collection if you want, but it's not specced into the language --- more about memory allocation later. C interfacing (at least with gnat) is trivial.

Basic features

The syntax is a bit Wirth. Here's 'Hello, world':

With Ada.Text_IO;

procedure Program is
begin
  Ada.Text_IO.Put_Line("Hello, world!");
end;

In fact, that's a theme you'll see throughout: the language is wordy, and deliberately so. It's to make it much harder to accidentally pair statements incorrectly --- so an if is always paired with an end if, and a loop with an end loop, and you never get dangling statements (e.g. the 'goto fail' bug). For extra robustness you can name blocks and use the name when closing them. In the above example, I could end the procedure with end Program.

All identifiers are case insensitive. Yes, it supports full Unicode. Yes, even Unicode identifiers are case insensitive! And no, the classic idiom in most other languages of having a type called Bitmap associated with a single instance called bitmap won't work.

It's got the usual block constructions you might expect. Conditionals:

if (a > 0) then
  Put_Line("positive");
else
  Put_Line("negative");
end if;

Conditional expressions:

Put_Line(if (a > 0) then "positive" else "negative");

(Semicolons are terminators --- look, even block statements need them!) Ordinary while loops:

a := 10;
while (a > 0) loop
  Put_Line("foo");
  a := a - 1;
end loop;

There's an sort-of-iterator-based for loop (more of what's actually going on here later):

for i in 1..10 loop
  Put_Line("foo");
end loop;

Breaks and bare loops:

loop
  Put_Line("foo");
  exit when (a == 0)
end loop

(I should add that I put parentheses around expressions because I grew up on C and think it improves clarity, but the language doesn't require it.) Named loops:

myloop: loop
  Put_Line("foo");
  exit myloop
end loop myloop -- required for a named loop

Switch statements:

case a is
  when 0 => Put_Line("zero");
  when others => Put_Line("others");
end case;

Switch statements must cover all possible input values --- for unbounded types like integers, a when others is mandatory. (There are case expressions, too, to match if expressions.)

This is all quite standard; nothing particularly exciting here, except for one surprising gotcha, which is that the and and or operators are not short-circuiting; use and then and or else instead.

Blocks are defined using declare..begin..end. The declare block is used for defining the block's variables. You can't (as far as I can tell) define variables inline with code, which is a bit old school. The declare can be omitted in function and procedure declarations.

declare
  a: integer := 42;
begin
  a := a + 1;
end;

Oddly, variables are not initialised by default, and like C, an uninitialised scalar variable may contain garbage. Non-scalar values like pointers are always initialised. Scalar values may contain invalid values, which are illegal to read from; this means that uninitialised variables may be invalid. There is a way to test at run-time whether a variable contains an illegal value.

Functions and procedures are defined in a fairly obvious manner; both input and output parameters are supported. Functions return a single value:

function Add(a, b: integer) return integer is
begin
  return 1;
end;

-- equivalent shortcut
function Add(a, b: integer) return integer is 1;

Procedures don't, so to return a value you need an output parameter:

procedure Add(a, b: in integer; result: out integer) is
begin
  result := a + b;
end;

Ada is, alas, a one-pass language, so things need to be prototyped if you're going to refer to them before they're defined.

Input parameters can have default values:

procedure Change(a: in out integer; b: integer := 1) is
begin
  a := a + b;
end;

Functions and procedures may be arbitrarily nested (but can, of course, only be defined in the declare block of the enclosing scope). Nested functions can refer to variables defined at a higher scope but, unfortunately, Ada doesn't have true closures --- you can't return a pointer to a nested function.

Keyword arguments are supported:

Add(result => outvar, a => 1, b => 2);

Plus you can omit the parentheses when calling zero-argument functions and procedures; which makes zero-argument functions indistinguishable from variables. (As far as I know, you can't fake setters.) Variadic functions and procedures are not supported at all, but you can fake them using array literals fairly easily.

And yes, Ada has goto.

Types

Here is where it starts to get interesting. You can define a type like this:

type MyType is new integer;

(That's not a type alias. That's a new type, based on integer. MyType and integer are not type compatible.) There are, of course, aggregate types, and they support default initial values:

type MyType is record
  a: integer;
  b: float := 99.7;
end record;

(I'm not sure why the new isn't required when defining records, to be honest.)

Scalar types can be constrained to a range.

type PercentageScore is new integer range 0..100;
type PercentageScore is range 0..100;  -- equivalent shorthand

The compiler will enforce the bounds at run time --- out-of-bound values throw exceptions.

The range doesn't need to be zero-based, and the base type doesn't need to be an integer:

type Change is new float range -1.0 .. +1.0;

You also get integer modulus, fixed-point and decimal types. The syntax is a little bit magic:

type Hour is mod 24;
type Fixed is delta 0.1 range -1.0 .. +1.0;
type Decimal is delta 0.1 digits 5;

All the above examples are discrete types. You can't assign an integer to a PercentageScore, for example. If you want this, you can use subtype:

declare
  subtype Percentage is integer range 0..100;
  
  p: Percentage;
  i: integer := 42;
begin
  p := i; -- allowed
  i := p; -- allowed
end

A bounds violation will cause a run-time error.

There are enumerations, and these can be very elegantly combined with subtypes:

type Days is (Mon, Tue, Wed, Thu, Fri, Sat, Sun);
subtype Workdays is Days range Mon..Fri;
subtype Weekend is Days range Sat..Sun;

Incredibly usefully, there's an in operator for determining membership of a type:

if (day in (Mon, Wed, Fri) then ... end if;
if (i in 0..5) then ... end if;
if (i in 3 | 5 | 7 | 9..11) then ... end if;

You can specify default values, too.

type Status is (On, Off, Unknown)
with
  default_value => Unknown;

You can apply arbitrary constraints and invariants to a type as part of the contract-based programming features; more on this later. Plus there's a whole set of interesting weird semantics to do with pointers and aliased types.

There's a native string type, but it's similar to Pascal; strings are arrays of characters and assignment from a string with a different length produces a run-time error. (Actually, it's cleverer than that. See the section below on strings.) There are variable-length string types in the standard library, but they're a bit cumbersome.

Type attributes

Now we start getting to the odd stuff.

There's a special operator, ', which allows the program to get information about a value or a type. Ada uses attributes where other language typically uses operators or builtin pseudofunctions. So, given the examples above:

declare
  d: Days;
begin
  d := Days'first; -- get first day of the week
  d := Days'succ(d); -- advance to next day

  d := Days'last; -- get last day of the week
  d := Days'succ(d); -- throw an exception
end;

There are a whole bunch of useful type attributes, including 'pred() (returns the previous item in an enumeration), 'pos() (returns an integer representation of a value), 'val() (converts an integer into the enumeration value), 'image() (returns a string repesentation of a value), etc.

And they work on other types too:

declare
  f: Fixed;
begin
  f := Fixed'first; -- get minimum possible value
  f := Fixed'succ(f); -- get next possible value
  Put_Line("not-quite-minimum value is " & Fixed'image(f)); 
end;

Some attributes only work on certain types --- so I can't use 'pos() on a Fixed, and I can't use 'succ() on a float.

Arrays

Ada has excellent support for managing arrays. They can be declared using a bounded type as the index:

type YearData is array(integer range 1..365) of integer;
type YearData is array(1..365) of integer; -- equivalent shortcut
type OnHoliday is array(Days) of boolean;

...and then accessed in the obvious way --- but note the use of () instead of []:

declare
  yd: YearData;
  oh: OnHoliday;
begin
  yd(1) := 7;
  oh(Mon) := true;
end;

There are aggregate initialisers (the same syntax works on records, too):

declare
  oh: OnHoliday := (Mon => true, others => false);
begin
  oh := (Mon => false, others => true);
end;

Multidimensional arrays are supported intrinsically --- although arrays of the form array(...) of array(...) of float are possible too.

declare
  type Bitmap is array(0..15, 0..15) of boolean;
  icon: Bitmap;
begin
  for x in 0..15 loop
    for y in 0..15 loop
      icon(x, y) := false;
    end loop;
  end loop;
end;

Array slicing works, but only between arrays of the same type, and only for single-dimensional arrays:

declare
  yd: YearData;
begin
  yd(1..10) := yd(2..11); -- overlapping ranges do the right thing
end

Yes, they work fine as lvalues, which allows these useful constructs to work:

declare
  yd: YearData;
begin
  yd(1..3) := (1, 2, 3);
  yd(3..365) := (others => 0); -- set values to zero
end;

Remember that & operator we saw above to concatenate strings? That actually contenates two compatible arrays, which allows this sort of thing to work:

declare
  distribution: array(0.99) of float;
begin
  distribution := distribution(0..49) & distribution(50..99);
end;

There are some useful attributes on arrays, as demonstrated:

declare
  yd: YearData;
begin
  for i in integer range yd'first .. yd'last loop
    yd(i) := i;
  end loop;
end;

However, there's also the 'range attribute. This returns a type, which represents the range of the array. This allows the above to be abbreviated to:

declare 
  yd: YearData;
begin
  for i in yd'range loop
    yd(i) := i;
  end loop;
end;

It works for multidimensional arrays too.

declare
  type Bitmap is array(0..15, 0..15) of boolean;
  icon: Bitmap;
begin
  for x in icon'range(1) loop
    for y in icon'range(2) loop
      icon(x, y) := false;
    end loop;
  end loop;
end;

What happens if you don't know the size of your array? You're in luck --- there's a special construct for that.

type Vector is array(integer range<>) of float;

These are a little bit deceptive. They don't represent an array which can change in size; they represent an array whose size is not known by the type system. They're implemented via a combination of fat pointers and fixed-size arrays, depending on context. They can be used as a shortcut in declaring variables, but they're mostly useful as parameters.

declare
  type Vector is array(integer range<>) of float; 

  -- Works on any size of Vector!
  function Sum(v: Vector) return float is 
    sum: float := 0.0;
  begin
    for f in v'range loop
      sum := sum + v(f);
    end loop;
    return sum;
  end;

  -- When we create the vector here, it gets assigned a concrete
  -- size.
  v: Vector := (0.0, 0.1, 0.2);
  s: float;
begin
  s := Sum(v);
  Put_Line("sum is " & float'image(s));
  s := Sum((1.1, 2.2, 3.3)); -- An array literal!
  Put_Line("other sum is " & float'image(s)); 
end;

Ada strings --- via the builtin string type --- are indefinite arrays of characters, and really demonstrate their power:

declare
  s1: string := "Fixed size string";
  s2: string := ReturnVariableLengthString();
  s3: string := "Compute " & "string " & "on the fly";
begin
  Put_Line("inline " & "computed " & "string");
  -- ...but can't reassign to s1, s2 or s3, because they cannot
  -- change size
end;

A brief note on calling conventions

At this point astute readers will be looking at the above and thinking: is that really passing a complete array as a parameter? Is this efficient? Are parameters passed by value or by reference?

The answer seems to be that while they're usually passed by reference, the language semantics mean that the question is irrelevant.

Procedure parameters can be declared as in, out, or in out. By default they're passed as in. Inside the procedure, parameters are immutable. In the Sum() function above, the array is being passed as an in parameter; because the compiler knows that the array cannot be modified inside the function, it can pass the parameter in by whatever mechanism it sees fit: by reference for large objects, by value for small ones.

When a parameter is passed as in out, then we've explicitly asked for the parameter to be passed by reference, because we want changes to the parameter to be reflected in the value being passed in. The same applies to out. (As a historical note, earlier versions of Ada forbade reading from out variables, which allowed more efficient calling conventions, but modern Ada allows it because otherwise people went insane.)

The result seems to be that Ada programmers simply don't care about the calling convention: they just write the code in the clearest possible way, and the compiler gets on with producing good code. Which is the correct way to do things, of course.

In fact, Ada code doesn't use pointers much. But it does have them, which brings us to...

Pointers

Now we're beginning to get a bit scary.

Ada has pointers; they're called access types, and they come in four main varieties.

The first is the pool access type. These must be named, can only point at values on the heap (specifically, on one specific heap; an Ada program may have many).

declare
  type PointerToHeapInt is access integer;
  pi: PointerToHeapInt;
begin
  pi := new integer; -- allocate from the pointer's heap
  pi.all := 42;
end; 

The .all is used to dereference the pointer. If you're pointing at a record, then it can be omitted, so you can use the same variable.member syntax you would use for a non-pointer.

The second form is the general access type. Like pool access types, these must be named, but these can point at values in any heap, or on the stack.

declare
  type PointerToStackInt is access all integer;
  i: aliased integer; -- allow taking a pointer
  pi: PointerToStackInt;
begin
  pi := i'access; -- get pointer to variable
  pi.all := 42;
end;

Only stack variables that have been marked as aliased can have their pointer taken.

The third are constant access types. Like general access types, these can point at anything, but they don't allow modification of the thing they're pointing at.

declare
  type ConstPointerToStackInt is access constant integer;
  i: aliased integer; -- allow taking a pointer
  pi: ConstPointerToStackInt;
begin
  pi := i'access; -- get pointer to variable
  -- Can't do this: pi.all := 42
end;

The fourth kind is the anonymous access type.

In Ada, when you define a type with the type keyword, you define a new type --- and two different types aren't compatible. (Use subtype instead of you want compatible types.) Therefore these two types cannot be used interchangeably:

type Pointer1 is access integer;
type Pointer2 is access integer;

An anonymous access is when you use the type directly in the variable declaration. Unlike with named types, this works:

declare
  p1: access integer;
  p2: access integer;
begin
  p1 := p2;
end;

Suprisingly, anonymous accesses seem to have the same semantics as general accesses, so an anonymous accesses can point at a stack object (I'd honestly have expected to need access all for that). This can cause a few issues, as Ada tries really, really hard to make sure that you don't leak pointers to local objects to a surrounding scope. For example, here is a function which reverses a list:

type Node is record
  next: access Node;
end record;

function reverselist(list: access Node) return access Node is
  result: access Node := null;
  this: access Node := list;
  next: access Node := null;
begin
  while this /= null loop
    next := this.next;
    this.next := result; -- [*]
    result := this;
    this := next;
  end loop;
  return result; -- [*]
end;

The two lines marked [*] will cause compilation failures on Ada 2005, because Ada 2005's type rules think there's a risk of local pointer leakage. Ada 2012's type rules are more sophisticated and will allow this code. By using a named pool access type instead of the anonymous access, we can assure that compiler that we can never be pointing at a stack object, and it'll be happy.

Preventing local pointer leakage is a big theme in Ada (they are, rightly, terrified of dangling pointers). The way this is done is painfully simple: access types carry with them the scope in which they were defined, and you may not assign a pointer to a local to an access type defined outside the local's scope. Consider this code:

declare
  type PtrType is access all integer;
begin
  declare
    i: aliased integer;
    ptr: PtrType;
  begin
    ptr := i'access; -- compilation error here
  end;
end;

That seems sensible enough, but this also fails to work:

declare
  type PtrType is access all integer;

  procedure Nop(param: PtrType) is
  begin
    null;
  end;

begin
  declare
    i: aliased integer;
  begin
    Nop(i'access); -- compilation error here
  end;
end;

Even though Nop() is totally safe to call, the type rules simply won't let you call it. So, yeah.

(In fact, pointers to local objects appear to be rarely used in Ada --- in and out parameters achieve the same effect in a vastly cleaner way.)

Ada also supports true references:

type Vector is array(integer range <>) of float;

procedure Show(values: Vector) is
begin
  for i in values'range loop
    declare
      item: float renames values(i);
    begin
      Put_Line(float'image(item));
    end;
  end loop;
end;

More types

Investigating the Ada type system is a bit like falling down a rabbit hole. You just keep falling, and you never know what you're going to find at the bottom...

Parameterised types? Of course!

declare
  type PixelStore is array(integer range <>, integer range <>) of boolean;
  pragma pack(PixelStore); -- pack multiple booleans per byte

  type Bitmap(width, height: positive) is record
    pixels: PixelStore(1..width, 1..height);
  end record;

  -- This procedure works on any size of bitmap!
  procedure FillBitmap(b: in out Bitmap) is
  begin
    -- We could just use b.pixels'range for this.
    for x in 1..b.width loop
      for y in 1..b.height loop
        b.pixels(x, y) := true;
      end loop;
    end loop;
  end;

  -- Creates a bitmap with a specific size.
  b: Bitmap(32, 32);
begin
  FillBitmap(b);
end;

Variant types? Yup.

declare
  type ColourMode is (RGB, CMYK);

  -- Type parameter has a default value.
  type Colour(mode: ColourMode := RGB) is record
    case mode is
      when RGB =>
        red, green, blue: float;
      when CMYK =>
        cyan, magenta, yellow, black: float;
    end case;
  end record;

  -- Create a default colour object --- will be of mode RGB.
  c: Colour;
begin
  -- Reassign the entire record. Only allowed because we declared c
  -- above with the default option.
  c := (CMYK, 1.0, 1.0, 1.0, 1.0);
end;

Explicitly non-null access types? Yup.

declare
  type Ptr is access integer;

  function Deref(p: not null Ptr) return integer is
  begin
    return p.all;
  end;

  i: aliased integer;
begin
  -- Throws an exception.
  i := Deref(null);
end;

(Alas, gnat seems unable to produce a compile-time error about the use of null above, so we get a run-time error instead. Since Ada catches null dereferences and turns them into thrown exceptions anyway, this is probably of limited use other than documentation.)

Bit-level control over record layouts? Ada originally came from the embedded world. Of course you can do this.

declare
  type RGB565 is record
    red, blue: integer range 0..(2**5 - 1);
    green: integer range 0..(2**6 - 1);
  end record;

  for RGB565 use record
    at mod 16; -- 16 bit alignment
    red at 0 range 0..4;
    green at 0 range 5..10;
    blue at 0 range 11..15;
  end record;

begin
  Put_Line("Size (in bits) is: " & integer'image(RGB565'size));
end;

(Interestingly, if I create a RGB565 on the stack, and then look at the size of the variable rather than the type, I get 128. Alignment issues, probably.)

Pointers to functions? Yes.

declare
  type Vector is array(integer range <>) of float;
  type AdjustCallback is access function(f: float) return float;

  procedure AdjustAll(v: in out Vector; cb: AdjustCallback) is
  begin
    for i in v'range loop
      v(i) := cb(v(i));
    end loop;
  end;

  function SetToZero(f: float) return float is
  begin
    return 0.0;
  end;

  v: Vector(0..10);
begin
  AdjustAll(v, SetToZero'access);
end;

...although bear in mind the pointer access rules; if AdjustCallback had been defined in an outer scope, we wouldn't be able to assign SetToZero() to it above (because of the risk of local object leakage).

Packages

No language is complete without a proper module system, and Ada is no exception.

package vector is
  type Vector is private;
    
  function Create(x, y: float) return Vector;
  function Length(v: Vector) return float;
    
private
  type Vector is record   
    x, y: float;
  end record;
    
  function Create(x, y: float) return Vector is
      (x => x, y => y); 
  function Length(v: Vector) return float is
      (Sqrt(v.x*v.x + v.y*v.y));
end;

Packages can have a public and a private part; any definitions in the private part (which are not prototyped in the public part) aren't exposed.

Functions and procedures must be defined out-of-line; the only exception are functions which return a single expression as above. We should be writing it like this:

package vector is
  type Vector is private;
    
  function Create(x, y: float) return Vector;
  function Length(v: Vector) return float;
  
private
  -- As in C and C++, the type definition must be exposed
  type Vector is record   
    x, y: float;
  end record
end;
  
package body vector is    
  function Create(x, y: float) return Vector is
      (x => x, y => y);
  function Length(v: Vector) return float is
      (Sqrt(v.x*v.x + v.y*v.y));
end;

The package definition and the package body correspond to the header and implementation, and can (but don't have to) be in different files. C and C++ programmers will find this very familiar.

Package bodies can have a begin and some code, useful for initialisation. And like everything else in Ada, packages can be nested arbitrarily; packages can be created in inner scopes.

Packages can refer to each other recursively; there's a whole complex mechanism for controlling package initialisation order which I won't go in to.

Contracts

Now we get to the good stuff.

Ada's designed for robust systems; it has excellent support for design-by-contract and invariants.

Let's say we're designing the world's most stupid FIFO. It can hold a single value; trying to fetch the value if none is stored, or storing a value if one is already stored, are illegal. We do it like this.

declare
  pragma Assertion_Policy(Check);
  subtype StoredValue is integer;

  hasvalue: boolean := false;
  value: StoredValue;

  procedure Store(newvalue: StoredValue)
  with
    pre => not hasvalue,
    post => hasvalue
  is begin
    value := newvalue;
    hasvalue := true;
  end;

  function Retrieve return StoredValue
  with
    pre => hasvalue,
    post => not hasvalue
  is begin
    hasvalue := false;
    return value;
  end;

begin
  Store(42);
  Store(99); -- throws an exception
end;

(This is Ada 2012 syntax. Ada 2005 still has preconditions and postconditions, but does them differently.) Surprisingly, we have to explicitly turn on invariant checks in gnat, as they're off by default.

Here, we're using the precondition to test to make sure that the caller of Store() and Retrieve() is using them properly; and the postcondition to make sure that the implementation of Store() and Retrieve() has done the right thing.

One unexpected annoyance is that you can only use preconditions and invariants on a procedure declaration, not the implementation. Which means that if you have a public procedure in a package, the invariants have to go in the package's header, which means they can't refer to any package private variables. I don't know why this is the case; it's a severe restriction on the usefulness of invariants, and while it's easy to work around, it's really ugly:

package Thing is
  procedure DoThing;
end;
  
package body Thing is
  privateVar: integer := 0;

  -- Private implementation has precondition on it; we're
  -- allowed this because DoThingImpl hasn't been prototyped    
  procedure DoThingImpl
  with
    pre => privateVar = 0
  is begin
    null;
  end;

  -- Public entry point just calls the implementation
  procedure DoThing is
  begin
    DoThingImpl;
  end;
end;

As a useful feature, postconditions can refer to the value of an expression on entry using the 'old attribute:

procedure increment(v: in out integer)
with
  post => v /= v'old
...

We can have arbitrary invariants on types, too.

type SmallVector is record   
  x, y: float;
end record
  with
    Dynamic_Predicate =>
      (SmallVector.x*SmallVector.x + SmallVector.y*SmallVector.y) <= 1.0;

Generics

Of course Ada has generics. Ada had generics before they were cool.

declare
  generic
    type T is private;
  procedure Swap(a, b: in out T);
 
  procedure Swap(a, b: in out T) is
    temp: T;
  begin
    temp := a;
    a := b;
    b := temp;
  end;
  
  procedure SwapInts is new Swap(integer);
  a: integer := 1;
  b: integer := 2;
begin
  SwapInts(a, b);
end;

They work very much like C++'s (although they're rather stricter than C++'s). Important things to note include that the generic procedure must be prototyped before the implementation --- you can't, as far as I can tell, combine them; and that there is no implicit instantiation of a generic. You must create (and name) one before you use it. So you don't get polymorphic functions.

(But because Ada supports overloading, you can instantiate the generic several times with the same name but different types, so you can simulate polymorphic functions moderately easily.)

Generic parameters don't have to be types; they can be values as well, allowing the traditional specify-size-of-container idiom that will be familiar to any C++ user:

declare
  generic
    size: positive;
    type T is private;  
  package RingBuffer is
    procedure Push(value: T);
    function Pop return T;
  end;
  
  package body RingBuffer is
    buffer: array(0..(size-1)) of T;    
    readptr: integer := 0;
    writeptr: integer := 0;
    
    procedure Push(value: T) is
    begin
      buffer(writeptr) := value;
      writeptr := (writeptr + 1) mod size;
    end;
    
    function Pop return T is
    begin
      readptr := (readptr + 1) mod size;
      return buffer(readptr);
    end;
  end;
  
  package RingBufferOfFloats is new RingBuffer(16, float);
begin
  RingBufferOfFloats.Push(77.0);
end;

The astute reader will think hey, modulus arithmetic --- isn't there a built in type which does that? and they'd be right. Unfortunately... the argument of a mod n type must be an actual constant, which size isn't, so we don't get to use modulus types here.

This highlights an important point about Ada's generics: while C++'s templates are, at their heart, macros, Ada's have to be completely syntactically and semantically valid. size in the example above is to all and intents and purposes not a constant, but a variable, even if it's actually implemented as a constant.

This is actually a good thing; the author of the package body above doesn't actually care that they're implementing a generic. They just write ordinary Ada like they would do any other day.

We can also use procedures as generic parameters. For example:

-- Definition

generic
  type T is private;
  with function Cost(element: T) return integer;
function CalculateCost(a, b, c, d: T) return integer;
  
function CalculateCost(a, b, c, d: T) return integer is
  (Cost(a) + Cost(b) + Cost(c) + Cost(d));

-- Instantiation

function SimpleCost(i: integer) return integer is (i);
function CostOfInts is new CalculateCost(integer, SimpleCost);

Here we're passing an an explicit function for calculating the cost of a thing. But we can also do this:

-- Definition

generic
  type T is private;
  with function Cost(element: T) return integer is <>;
function CalculateCost(a, b, c, d: T) return integer;
  
function CalculateCost(a, b, c, d: T) return integer is
  (Cost(a) + Cost(b) + Cost(c) + Cost(d));

-- Instantiation

function Cost(i: integer) return integer is
  (i);
  
function CostOfInts is new CalculateCost(integer);

The is <> tells the compiler that instead of being passed the function explicitly, it should be pulled in from the scope when the generic is instantiated. The result is that we can use any type for T provided T supports the Cost() operation.

There's a large and frankly rather complicated set of tools for specifying generic type parameters; it's possible to build up arbitrarily complex generic type expressions. However, Ada doesn't do type inference of any kind, so if you want a parameter which is an arbitrary array of modulus types you need to specify each generic part explicitly when instantiating the generic:

generic
  type R is range <>;
  type E is mod <>;
  type S is array(R) of E;
package Thing is
  ...
end;

type MyR is integer range 10..20;
type MyE is mod 7;
type MyS is array(MyR) of MyE;
package MyThing is new Thing(MyR, MyE, MyS);

Object-oriented programming

Of course Ada has... you get the picture.

Ada's support for object oriented code is actually rather similar to C++'s conceptually, although the syntax is different.

An Ada class is a tagged record defined in a package. Methods are just procedures (and functions) which use the record as the first parameter.

package ObjectPackage is
  type Object is tagged record
    null; -- no members right now
  end record;

  function Hash(o: Object) return integer;
end;
  
package body ObjectPkg is
  function Hash(o: Object) return integer is (0);
end;

Tagged records keep vtables to support dynamic dispatch and subclassing.

Calling a method on an object is simply:

declare
  use ObjectPkg; -- import definitions from package
  o: Object; -- create object
  i: integer;
begin
  i := Hash(o);
end;

(I don't know why there's the requirement that tagged records must live packages --- it seems very restrictive to me, as you can't declare tagged records ad hoc in procedures. Particularly as subclasses don't have to be in a package and can be created anywhere.)

There's a piece of syntactic sugar which allows methods on objects in this way to be called like this:

i := o.Hash;

This cannot be used on non-tagged records. It can, though, be used on accesses to records --- you don't need to dereference the access explicitly.

Classes can, of course, be subclassed:

package AnimalsPkg is
  type Animal is tagged null record;
  procedure Vocalise(creature: Animal);
    
  type Dog is new Animal with null record;
  procedure Vocalise(creature: Dog);
end;
  
package body AnimalsPkg is
  procedure Vocalise(creature: Animal) is
  begin
    Put_Line("[sound effect of cells metabolising]");
  end;
    
  procedure Vocalise(creature: Dog) is
  begin
    Put_Line("woof");
  end;  
end;

(null record is shorthand for record null; end record. Also, it's common to put the class record in the private part of the package definition so that users can't access it. I've omitted that here for simplicity.)

Calls to the superclass are done by casting the object to the superclass and calling the method on that:

type Poodle is new AnimalsPkg.Dog with null record;

procedure Vocalise(creature: Poodle) is
begin
  Put_Line("In French:");
  Dog(creature).Vocalise;
end;

(The above code demonstrates subclassing from outside the package --- it makes the example slightly shorter.) The call to AnimalsPkg.Dog() provides a view onto creature of type Dog.

The astute reader will note that if I'm casting the Poodle to a Dog and calling Vocalise() on it, then we can't be doing dynamic dispatch. That's correct. In all the above examples, we're calling methods directly using static dispatch.

Unlike in C++, where the decision to use dynamic dispatch is a property of the method, in Ada it's a property of the type used to hold the object. To create a type capable of dynamic dispatch, we use the 'class attribute. These can hold an instance of the class or any subclass.

declare
  package AnimalsPkg is
    type Animal is abstract tagged null record;
    procedure Vocalise(creature: Animal) is abstract;
    
    type Dog is new Animal with null record;
    procedure Vocalise(creature: Dog);

    type Cat is new Animal with null record;
    procedure Vocalise(creature: Cat);        
  end;
  
  package body AnimalsPkg is
    procedure Vocalise(creature: Dog) is
    begin
      Put_Line("woof");
    end;
    
    procedure Vocalise(creature: Cat) is
    begin
      Put_Line("meow");
    end;
  end;
  use AnimalsPkg;

  procedure Kick(creature: Animal'Class) is
  begin
    creature.Vocalise;
    Put_Line("...you fiend.");
  end;
  
  mydog: Dog;
  mycat: Cat;
begin
  Kick(mydog);
  Kick(mycat);
end;

Oh, and by the way, Ada support abstract classes too.

'class types are magic in the same way that string or array(<>) are; they can be initialised from a real instance, or used as parameters, but not actually created anywhere. They're most commonly used in access types:

type AnimalRef is access Animal'class;

Ada supports interfaces, and they work in the obvious way:

type Bitey is interface;
...
type Dog is new Animal and Bitey with null record;

Const methods are supported --- in fact, all the above examples are const; that first parameter needs to be declared in out if you want them to be able to modify the object.

RTTI is supported, via the in operator described above.

Multiple inheritance is not supported, which may or may not be a good thing, but there is special (if slightly baroque) support for mixins.

Constructors are supported, sort of. In a real Ada program, each class would live in its own package, and would look like this:

package DeadlySeriousBusinessPackage is
  type Object is tagged private;
  type ObjectRef is access Object'class;
    
  function Create return ObjectRef;    
private
  type Object is tagged null record;
end;
  
package body DeadlySeriousBusinessPackage is
  function Create return ObjectRef is
    this: ObjectRef := new Object;
  begin
    return this;
  end;
end;

The Create function can do any construction it feels necessary before returning the access to the object to the caller.

Destructors are supported, sort of, as are copy constructors. There's a magic base class, Ada.Finalization.Controlled, which provides Initialise, Adjust and Finalize methods:

type FileHandle is new Ada.Finalization.Controlled with null record;
procedure Finalize(this: in out FileHandle) is
begin
  Put_Line("free handle here");
end;

Operator overloading is supported:

function "*" (left, right: Matrix) return Matrix;

All operators can be overloaded, including the textual ones like not and and; but, of course, things like and then and in are not operators and cannot be overloaded.

Concurrency part 1: tasks

Of course Ada etc etc.

Ada's concurrency model is rather elegant, and is based around message passing and state machines.

The first form is the task: a background thread which exposes an interface which looks like an object, on which we can call methods. Each method call translates to a synchronous message send to the thread, which can accept them in any order it wishes. It's easiest to explain with an example:

declare
  task Fifo is
    entry Push(value: in integer);
    entry Pop(value: out integer);
  end;
  
  task body Fifo is
    i: integer;
  begin
    loop
      accept Push(value: in integer) do
        i := value;
      end;
      accept Pop(value: out integer) do
        value := i;
      end;
    end loop;
  end;
  
  i: integer;
begin
  Fifo.Push(7);
  Fifo.Pop(i);
end;

When the enclosing scope returns, it will automatically block until the task exits --- don't run the above example, it'll hang indefinitely. Incidentally, note that the above code is living inside a simple declare..begin..end block. You can embed throwaway tasks in any piece of code you like.

It's possible to wait for more than one message at a time. Here's a restructured version of the above, which also demonstrates clean termination:

declare
  task Fifo is
    entry Push(value: in integer);
    entry Pop(value: out integer);
  end;

  task body Fifo is
    i: integer;
  begin
    loop
      select
        accept Push(value: in integer) do
          i := value;
        end;
      or
        accept Pop(value: out integer) do
          value := i;
        end;
      or
        terminate;
      end select;
    end loop;
  end;

  i: integer;
begin
  Fifo.Push(7);
  Fifo.Pop(i);
end;  

The or terminate clause tells the task to automatically exit if there are no more messages to send and the owner of the task (i.e. the task's enclosing scope) has exited.

If a message is sent to a task which it's not ready for, then the caller blocks until the task is ready. This sounds like a deadlock, but it's not: the task's state may change due to events sent by another task. Consider the following:

declare
  task Waiter is
    entry Wait;
    entry BeKicked;
  end;

  task body Waiter is
  begin
    accept BeKicked;
    accept Wait;
  end;
    
  task Kicker;
  task body Kicker is
  begin
    delay 1.0;
    Waiter.BeKicked;
  end;    
begin
  Waiter.Wait;
end;

Waiter won't accept a Wait message until it's processed the BeKicked entry, which is provided by the Kicker task. In the mean time, the main thread happily blocks until Waiter has been kicked. (delay is Ada's built-in sleep operation. It also does a whole raft of other cool things. See below.)

It's possible to make entries conditional on the task state:

select
  when not fifofull =>
    accept Push(value: in integer) do
      ...
    end;
end select;

The caller will remain blocked until the task is capable of handling the call.

Timeouts can be done on both ends, using pleasingly symmetrical syntax:

declare
  task Dodgy is
    entry Wait;
  end;

  task body Dodgy is
  begin
    select
      accept Wait;
    or
      delay 5.0;
      Put_Line("task gave up");
    end select;
  end;
begin
  select
    Dodgy.Wait;
  or
    delay 5.0;
    Put_Line("caller gave up");
  end select; 
end;

Tasks can be created dynamically:

declare
  task type Dodgy is
    ...as above...
  end;
  
  task body Dodgy is
    ...as above...
  end;

  mydodgy: Dodgy;
begin
  mydodgy.Wait;
end;

You can even create them on the heap or in arrays. Try:

mydodgy: access Dodgy := new Dodgy;

Tasks can also be killed asynchronously using the abort keyword, although for safety it's possible for a task to have unabortable sections which must be atomic.

Concurrency part 2: protected types

Tasks are awesome, but sometimes they're not quite what you want --- particularly as there's no protection against two tasks modifying the same variable at the same time.

This is where protected types come in. They are, essentially, data structures wrapped in an automatic reader/writer lock. They look a lot like packages:

declare
  protected Fifo is
    procedure Push(value: in integer);
    procedure Pop(value: out integer);
  private
    i: integer;
  end;

  protected body Fifo is
    procedure Push(value: in integer) is
    begin
      i := value;
    end;
      
    procedure Pop(value: out integer) is
    begin
      value := i;
    end;
  end;
    
  i: integer;
begin
  Fifo.Push(7);
  Fifo.Pop(i);
end;

All calls to Push and Pop will now be serialised, regardless of the task they came from.

Some important points:

  • the data itself must be defined in the declaration, not the body;
  • all data must be private;
  • you can have procedures or functions in the protected type, but they work differently; procedures get a reader/writer lock, functions get a reader lock only and don't have write access to the protected type's data.

You can also define entries in the protected type. These work as for tasks, and behave like procedures, but you get to use select, guards etc on them. Weirdly, for protected types, entries must have guards. I won't bother going into the syntax; it's a bit esoteric.

Just like for tasks, you can create named protected types and instantiate them repeatedly. The syntax is identical, using protected type instead of task type.

A brief note on time

The example above showed the delay keyword. There are actually some rather interesting things you can do with this.

Consider a simple timer task:

task Timer;
task body Timer is
begin
  for i in 1..10 loop
    delay 1.0;
    Receiver.Tick;
  end loop;
end;

This will gradually drift due to the time taken to execute Receiver.Tick, which adds extra time on to each iteration. So we do this instead:

task Timer;
task body Timer is
  use Ada.Calendar; -- needed for Time type and Clock function
  nexttick: Time := Clock; -- initialise to current time
begin
  for i in 1..10 loop
    nexttick := nexttick + 1.0;
    delay until nexttick;
    Receiver.Tick;
  end loop;
end;

delay until can be used anywhere that delay can.

What if we want an operation to take at most a certain amount of time, rather than at least? We can do that as well, and now we're beginning to get well out of C++ territory:

declare
  count: integer := 0;
begin
  select
    delay 1.0;
  then abort
    loop
      count := count + 1;
    end loop;
  end select;
  Put_Line("iterations per second: " & integer'Image(count));
end;

Once the loop has run for one second, it will be terminated (using the same abort mechanism that works for tasks).

Actually, I've cheated slightly above. The implementation is only required to honour an abort when a task interacts with the outside world. As the loop above is pure code and does not do this, gnat (which I'm using for testing) won't abort it. So we need to do this instead:

loop
  delay 0.0; -- abort may occur here
  count := cont + 1;
end loop;

Anyone who's used pthreads and cancellation points will find this familiar.

Dynamic memory allocation

So far I've mentioned allocating values off the heap using the new keyword, but I haven't mentioned how to free them again. There's a reason for this, which is:

The Ada core language does not have any mechanism to free memory.

This seems really surprising, but there's actually a good reason for this. Freeing memory is a fundamentally unsafe operation: by its very nature, it causes pointers to become invalid. It's only safe to do at all if you have in your hand the last remaining pointer to the object, and the language has no way to guarantee this.

(Plus, of course, Ada has its roots in embedded systems, which don't really do dynamic allocation.)

So, the Ada language suggests you either: (a) statically allocate everything, using globals or the stack; (b) recycle dynamically allocated objects yourself by keeping unused ones on free lists; (c) use garbage collection.

Naturally, in the real world, people do (d), which is to cheat. There's a generic function in the standard library called Ada.Unchecked_Deallocation, which frees memory to the heap. This bypasses all the language semantics --- the clue's in the name! --- and allows you to shoot yourself in the foot to your heart's content.

It's used like this:

declare
  type Thing is record
    value: integer;
  end record;
  type ThingRef is access Thing;
    
  function NewThing return ThingRef is
  begin
    return new Thing;
  end;
    
  procedure FreeThing is new Ada.Unchecked_Deallocation(
     Thing, ThingRef);
           
  p: ThingRef;
begin
  p := NewThing;
  FreeThing(p);
end;  

Important things to note include that you must instantiate Unchecked_Deallocation for each type you want to free --- you must carefully aim the compiler at each foot you want to shoot off; you need to tell it both the type of the object and the object's pointer; and the instantiated function's parameter is of mode in out and p will be set to null on return.

The function will only accept objects via the pointer that you specified when you instantiated the function. This is so that it knows what heap the object came from. Ada allows multiple concurrent storage heaps.

The syntax is as follows:

declare
  type Thing is new integer;
  type ThingRef is access Thing;
  for ThingRef'storage_pool use myCustomStoragePool;

  p: ThingRef;
begin
  p := new Thing;
end;

The new Thing that is assigned to p will use myCustomStoragePool.

Storage pools are just classes with some methods for doing allocation and deallocation, and can be created anywhere. For example, one of the standard pool classes is System.Pool_Local.Unbounded_Reclaim_Pool, which is an unbounded pool which frees its storage when it goes out of scope:

declare
  localPool: System.Pool_Local.Unbounded_Reclaim_Pool;
  type Thing is new integer;
  type ThingRef is access Thing;
  for ThingRef'storage_pool use localPool;

  p: ThingRef := new Thing;
begin
  -- do something with p here
  -- all ThingRef pointers will be freed automatically when the block exits
end;

The storage pool is a property of the pointer, not the object; pool accesses that refer to different pools are not compatible (even if they're pointing to the same kind of object). General accesses --- access all Thing --- can point anywhere, as can constant accesses.

This has a lot of utility in the embedded world: consider a segmented architecture like the 8086, for example. Each segment register can point to a different address space. The compiler needs to know which one, so that it can generate code using the appropriate segment register. Ada can represent this semantic directly in code by using different storage pools to represent each segment register, and access all types would use a fat pointer representation which can point (inefficiently) to any segment.

Exceptions

Of course etc.

Exceptions are a bit weird --- they're not values as they are in most modern languages; they're just error tags:

declare
  Fnord: exception; -- not a variable declaration; this syntax is magic
begin
  raise Fnord;
exception
  when Fnord =>
    Put_Line("Fnord caught!");
  when others =>
    Put_Line("Something else caught? Rethrowing");
    raise;
end;

The amount of information that can be attached to an exception is rather minimal.

declare 
  Fnord: exception;
begin
  raise Fnord with "Unexpected fnord seen";
exception
  when e: Fnord =>
    Put_Line("Fnord caught! " & Exception_Message(e));
end;

The name of a caught exception can be fetched with Exception_Name(); it'll be qualified according to the scope the exception was defined in, so two exceptions with the same identifier will be distinguishable. There's a library package for doing more interesting things with exceptions, like saving them for later.

As far as I know there's no language facility for getting stack traces, but GNAT has an extension.

C interoperability

Of course, no language is any use if it can't talk to libraries, and libraries are written in C.

Of course Ada can talk to C.

In fact, it's astonishingly easy:

package body CInterface is
  procedure Import_From_C;
  pragma import(C, Import_From_C);
  
  procedure Export_To_C;
  pragma export(C, Export_To_C);
end;

(Of course, Export_To_C actually needs to be defined somewhere.)

Types are converted in a reasonably sane fashion; the rules are actually laid out in the Ada specification --- this isn't a compiler extension. The Interfaces.C package also contains definitions of all the C native types, and provides useful functions for converting C strings into Ada strings and vice versa. pragma convention can be used to specify whether records should be passed by reference or by value.

But most of the time, it really is as easy as the example above.

Containers

Ada's container library is strangely similar to C++'s... for very good reasons; C++'s STL was written by the same person who had previously written Ada's.

This is both a good thing and a bad thing. It's good because it's powerful and very flexible; it's bad because it's not particularly user-friendly, although it's saner than C++'s. At least in Ada it's much harder to shoot yourself in the foot than it is in C++.

declare
  use Ada.Containers;

  package MyVector is new Vectors(
      Index_Type => positive, Element_Type => integer);
  
  v: MyVector.Vector;
begin
  v.Append(7);
  v.Append(42);
  v.Append(-9);
  Put_Line("Length is: " & Count_Type'image(v.Length));
end;

Idiom seems to be that you don't instantiate them on the fly; instead you embed them in data-structure specific packages, so if you need a vector of Things you use the Thing.Vector datatype (which stores Thing.Objects).

These all use dynamic memory allocation behind the scenes but, hopefully, safely.

There are Java-style iterators:

procedure List(v: MyVector.Vector) is
  use MyVector;
  c: Cursor := v.First;
begin
  while Has_Element(c) loop
    Put_Line("seen element: " & integer'Image(Element(c)));
    Next(c);
  end loop;    
end;

Like C++, Ada.Containers frequently uses cursors as generic pointers into a container, but it's more liberal than the STL --- you can usually use indices instead (if appropriate for the container). Cursors are not tagged types, which means we don't get to use method call syntax on them, which is a pity.

Given Ada's excellent support for nested functions, it would be astonishing if there weren't callback-style iterators, and of course there are:

procedure List(v: MyVector.Vector) is
  use MyVector;
  procedure cb(c: Cursor) is
  begin
    Put_Line("seen element: " & integer'Image(Element(c)));
  end;  
begin
  v.Iterate(cb'Access);
end;

There's all the usual container-based cool stuff here, including some generic algorithms; I won't go into the details --- interested parties can dig up the documentation.

Summing up

Naturally, this is a personal opinion only, but:

Ada is awesome. It's like C++ wants to be if it ever grew up. It's fast but safe; it's elegant and expressive but also streamlined. Where C and C++ tend to focus on the lowest-level features possible, Ada tends to use higher level constructs which can still be implemented in a low-level way. So C has pointers; Ada has accesses, which may be implemented in several different ways depending on context, but the user doesn't need to care. C has mutexes and threads; Ada has protected types and tasks and rendezvous-based RPC (which I have, in fact, been using for years in C and C++ but have only just found out the name of). C has types which correspond to various sizes of machine word; Ada defines types by the problem they're trying to solve, and then maps them efficiently onto machine word representations.

Ada's biggest draw is that you can write programs in it which make sense --- you get to focus on the problem rather than the implementation. All those high-level features are focused on actually getting stuff done.

For example: further down here is a link to a multithreaded Mandelbrot renderer I wrote. The core of the renderer contains a pool of worker threads and a scheduler which assigns work units to them. Total amount of code? About 50 lines, most of which are comments. Total amount of thought? I'll admit that I didn't get it right the first time (because I'd overthought it, ironically), but it certainly worked the second time.

Knowing that I get to use these high level features and that I'm still going to get good performance is the icing on the cake. The Computer Language Benchmarks Game shows that Ada 2005 and C++ are pretty much indistinguishable, performance-wise; Ada wins some, C++ wins some.

I find myself wondering why I should write in C++ any more --- doing the same job in Ada is going to be easier, more intrinsically robust, and will produce similar-sized binaries that run at the same speed...

That's not to say it's perfect. It's not. Ada has warts, and plenty of them.

The biggest, in my opinion, is also one of Ada's its greatest strengths: it doesn't have any implicit memory allocation anywhere. The only place (outside the standard libraries) which allocates memory is the new keyword.

This means that you can be absolutely sure how much memory your application needs, but it also means that the language can't do a whole bunch of really cool things which most modern languages now have --- such as persistant closures and ad-hoc data structures. There are features which help a lot, such as array(integer range <>), but there are some language features which just need a heap allocation, and Ada doesn't have any of these.

In addition, Ada's relationship with freeing memory is kinda disfunctional (via Ada.Unchecked_Deallocation). I understand the reasoning why it's so strange, and I think that this approach is the least bad one the designers could have taken, but it's a massive hole in the otherwise bulletproof robustness of the language.

Personally, I think that the original Ada designers wanted a garbage collector --- a relaxed-rules Ada with closures, inline maps, the ability to have range<> arrays in structures, variable-length strings etc would be totally epic. Unfortunately not only does such a thing not exist, but I have yet to find an implementation that even has a garbage collector. Go figure. (Searching for 'gnat garbage collector' finds a lot of references to insect repellent.)

There's other stuff wrong, as well: it being case insensitive bugs me (What is this, QuickBasic? These days every programmer knows and uses case in identifiers to convey actual semantic meaning. Not being able to do this in Ada is a pain. Plus I'm sure there are endless Unicode edge cases which will cause confusion way down the line). It being a one-pass compiler bugs me (there is no excuse for a modern language to require forward declarations). The missing really obvious language features bug me (if I can do exit when, we can't I use when on any other statement?). Some of the type system oddities bug me (I can't use range<> directly in a procedure definition? Why not?). The standard library bugs me (strings vs wide strings vs wide wide strings aaargh! HULK SMASH).

But this is all pretty minor stuff. All programming languages suck; Ada sucks in surprisingly minor ways. And if that sounds like faint praise, that's just because I'm cynical and jaded from years of struggling with terrible programming languages. Ada is awesome.

References

Here are some interesting links which... you may be interested in.

  • You may be interested in a multithreaded Mandelbrot renderer which I hacked up in Ada. It's a more substantial example than the ones above, and even though it's not very well written, it demonstrates the elegance and power of the task functionality. The most complex and time-consuming part was the output (I think ideone's wide character support for Ada is kinda borken).
  • ideone, where the above is hosted, is really useful for playing with snippets of Ada; I tested most of the examples here on it. Do be aware that it doesn't support Ada 2012 (as far as I can tell).
  • For more serious programs, you want the gcc-based GNAT toolchain. This is the de-facto standard industrial strength Ada compiler. It even comes with the GPS Ada IDE, which is old-school and a bit quirky, but works really well. Linux users can find the gnat-gps package in their local repository. It'll produce real, fast, standalone binaries and there's an integrated debugger. However, beware: at least some versions, including the binaries that are available from Libre, have dodgy licensing which means that all your binaries must be licensed under the GPL. Check carefully.
  • For documentation... well, to be honest, I haven't found a good source yet. (If you know of one, let me know.) Writing this article took a lot of research. WikiBooks has a good book on Ada Programming, which I used heavily as a reference, but it's annoyingly vague on some of the details. The official Ada specification is available. Do not read it or your brain will melt. I will recommend the Ada 2012 Rationale, which makes fascinating reading as it explains why the a lot of the features exist, and is really useful to figure out what strange term Ada uses to refer to some standard language feature, so you can go look it up; but of course it's mostly talking about Ada 2012 features.