Rationale for Ada 2012
6.3 Iteration
Iteration and subprogram
calls are in some sense the twin cornerstones of programming. We are
all familiar with the ubiquitous nature of statements such as
for I in A'Range loop
A(I) := 0;
end loop;
which in one form or another exist in all (normal)
programming languages.
The detail of giving the precise description of the
iteration and the indexing is really a violation of abstraction by revealing
unnecessary detail. All we want to say is "assign zero to each element
of the set A".
However, although it's
not too much of a hassle with arrays, the introduction of containers
revealed that detailed iteration could be very heavy-handed. Thus, as
mentioned in the Introduction (see
1.3.5),
suppose we are dealing with a list, perhaps a list of the type
Twin
declared as
type Twin is
record
P, Q: Integer;
end record;
To manipulate every
element of the list in Ada 2005, we have to write something like
C := The_List.First; -- C declared as of type Cursor
loop
exit when C = No_Element;
E := Element(C); -- E is of type Twin
if Is_Prime(E.P) then
Replace_Element(The_List, C, (E.P, E.Q + X));
end if;
C := Next(C);
end loop;
This reveals the gory details of the iterative process
whereas all we want to say is "add X
to the component Q for all members of the
list whose component P is prime".
There is another way
in Ada 2005 and that is to use the procedure
Iterate.
In that case the details of what we are doing have to be placed in a
distinct subprogram called perhaps
Do_It.
Thus we can write
declare
procedure Do_It(C: in Cursor) is
begin
E := Element(C); -- E is of type Twin
if Is_Prime(E.P) then
Replace_Element(The_List, C, (E.P, E.Q + X));
end if;
end Do_It;
begin
The_List.Iterate(Do_It'Access);
end;
This avoids the fine detail of calling First
and Next but uses what some consider to be
a heavy infrastructure.
However, in Ada 2012
we can simply say
for E of The_List loop
if Is_Prime(E.P) then
E.Q := E.Q + X;
end if;
end loop;
Not only is this just five lines of text rather than
nine or eleven, the key point is that the possibility of making various
errors of detail is completely removed.
The mechanisms by which this magic abstraction is
achieved are somewhat laborious and it is anticipated that users will
take a cookbook approach (show us how to do it, but please don't explain
why – after all, this is the approach taken with boiling an egg,
we can do it without deep knowledge of the theory of coagulation of protein
material).
We will start by looking
at the process using arrays. Rather than
for I in A'Range loop
if A(I) /= 0 then
A(I) := A(I) + 1;
end if;
end loop;
we can write
for E of A loop
if E /= 0 then
E := E + 1;
end if;
end loop;
In the case of a two-dimensional
array, instead of
for I in AA'Range(1) loop
for J in AA'Range(2) loop
A(I, J) := 0.0;
end loop;
end loop;
we can write
for EE of AA loop
EE := 0.0;
end loop;
In Ada 2005 (and indeed
in Ada 95 and Ada 83), the syntax for a loop is given by
loop_statement ::= [loop_statement_identifier :]
[iteration_scheme] loop
sequence_of_statements
end loop [loop_identifier] ;
iteration_scheme ::= while condition
| for loop_parameter_specification
loop_parameter_specification ::= defining_identifier in [reverse] discrete_subtype_definition
This is all quite familiar.
In Ada 2012, the syntax for loop_statement remains the same but iteration_scheme
is extended to give
iteration_scheme ::= while condition
| for loop_parameter_specification
| for iterator_specification
Thus the new form iterator_specification
is introduced which is
iterator_specification ::=
defining_identifier in [reverse] iterator_name
| defining_identifier [: subtype_indication] of [reverse] iterable_name
The first production defines a
generalized iterator
whereas the second defines an
array component iterator or a
container
element iterator. For the moment we will just consider the second
production which has
of rather than
in. The
iterable_name
can refer to an array or a container. Suppose it is an array such as
A or
AA in the
examples above.
We note that we can
optionally give the subtype of the loop parameter. Suppose that the type
A is given as
type A is array (index) of Integer;
then the subtype of the loop parameter (E
in the example) if not given will just be that of the component which
in this case is simply Integer. If we do give
the subtype of the loop parameter then it must cover that of the component.
This could be useful with tagged types.
Note carefully that the loop parameter does not have
the type of the index of the array as in the traditional loop but has
the type of the component of the array. So on each iteration it denotes
a component of the array. It iterates over all the components of the
array as expected. If reverse is not specified then the components
are traversed in ascending index order whereas if reverse is specified
then the order is descending. In the case of a multidimensional array
then the index of the last dimension varies fastest matching the behaviour
of AA in the expanded traditional version
as shown (and which incidentally is the order used in streaming). However,
if the array has convention Fortran then it is the index of the first
dimension that varies fastest both in the case of the loop and in streaming.
There are other obvious rules. If the array A
or AA is constant then the loop parameter
E or EE is also
constant. So it all works much as expected. But do note carefully the
use of the reserved word of (rather than in) which distinguishes
this kind of iteration from the traditional form using an index.
As another array example
suppose we have the following
type Artwin is array (1 .. N) of Twin;
The_Array: Artwin;
which is similar to
the list example above. In the traditional way we might write
for K in Artwin'Range loop
if Is_Prime(The_Array(K).P) then
The_Array(K).Q := The_Array(K).Q + X;
end if;
end loop;
Using the new notation
this can be simplified to
for E: Twin of The_Array loop
if Is_Prime(E.P) then
E.Q := E.Q + X;
end if;
end loop;
where we have added
the subtype Twin to clarify the situation.
Similarly, in the simple list example we could write
for E: Twin of The_List loop
if Is_Prime(E.P) then
E.Q := E.Q + X;
end if;
end loop;
Note the beautiful similarity between these two examples.
The only lexical difference is that The_Array
is replaced by The_List showing that arrays
and containers can be treated equivalently.
We now have to consider how the above can be considered
as behaving like the original text which involves C
of type Cursor, and subprograms First,
No_Element, Element,
Replace_Element and Next.
This magic is performed
by several new features. One is a generic package whose specification
is
generic
type Cursor;
with function Has_Element(Position: Cursor) return Boolean;
package Ada.Iterator_Interfaces is
pragma Pure(Iterator_Interfaces);
type Forward_Iterator is limited interface;
function First(Object: Forward_Iterator) return Cursor is abstract;
function Next(Object: Forward_Iterator; Position: Cursor)
return Cursor is abstract;
type Reversible_Iterator is limited interface and Forward_Iterator;
function Last(Object: Reversible_Iterator) return Cursor is abstract;
function Previous(Object: Reversible_Iterator;
Position: Cursor) return Cursor is abstract;
end Ada.Iterator_Interfaces;
This generic package
is used by the container packages such as Ada.Containers.Doubly_Linked_Lists.
Its actual parameters corresponding to the formal parameters Cursor
and Has_Element come from the container which
includes an instantiation of Ada.Iterator_Interfaces.
The instantiation then exports the various required types and functions.
Thus in outline the relevant part of the list container now looks like
with Ada.Iterator_Interfaces;
generic
type Element_Type is private;
with function "=" (Left, Right: Element_Type) return Boolean is <>;
package Ada.Containers.Doubly_Linked_Lists is
...
type List is tagged private ...
...
type Cursor is private;
...
function Has_Element(Position: Cursor) return Boolean;
package List_Iterator_Interfaces is
new Ada.Iterator_Interfaces(Cursor, Has_Element);
...
...
end Ada.Containers.Doubly_Linked_Lists;
The entities exported from the generic package
Ada.Iterator_Interfaces
are the two interfaces
Forward_Iterator and
Reversible_Iterator. The interface
Forward_Iterator
has functions
First and
Next
whereas the
Reversible_Iterator (which is
itself descended from
Forward_Iterator) has
functions
First and
Next
inherited from
Forward_Iterator plus additional
functions
Last and
Previous.
Note carefully that a Forward_Iterator
can only go forward but a Reversible_Iterator
can go both forward and backward. Hence it is reversible and not Reverse_Iterator.
The container packages
also contain some new functions which return objects of the type Reversible_Iterator'Class
or Forward_Iterator'Class. In the case of
the list container they are
function Iterate(Container: in List) return
List_Iterator_Interfaces.Reversible_Iterator'Class;
function Iterate(Container: in List; Start: in Cursor) return
List_Iterator_Interfaces.Reversible_Iterator'Class;
These are new functions and are not to be confused
with the existing procedures
Iterate and
Reverse_Iterate
which enable a subprogram to be applied to every element of the list
but are somewhat cumbersome to use as shown earlier. The function
Iterate
with only one parameter is used for iterating over the whole list whereas
that with two parameters iterates starting with the cursor value equal
to
Start.
Now suppose that the
list container is instantiated with the type Twin
followed by the declaration of a list
package Twin_Lists is
new Ada.Containers.Doubly_Linked_Lists(Element_Type => Twin);
The_List: Twin_Lists.List;
So we have now declared
The_List which is a list of elements of the
type Twin. Suppose we want to do something
to every element of the list. As we have seen we might write
for E: Twin of The_List loop
... -- do something to E
end loop;
However, it might be
wise at this point to introduce the other from of iterator_specification
which is
defining_identifier in [reverse] iterator_name
This defines a generalized
iterator and uses the traditional in rather than of used
in the new array component and container element iterators. Using this
generalized form we can write
for C in The_List.Iterate loop
... -- do something via cursor C
end loop;
In the body of the
loop we manipulate the elements using cursors in a familiar way. The
reader might wonder why there are these two styles, one using in
and the other using of. The answer is that the generalized iterator
is more flexible; for example it does not need to iterate over the whole
structure. If we write
for C in The_List.Iterate(S) loop
then the loop starts
with the cursor value equal to S; this is
using the version of the function Iterate
with two parameters. On the other hand, the new array component and container
element iterators using of are more succinct where applicable.
The generalized iterators
for the list container use reversible iterators because the functions
Iterate return a value of the type
Reversible_Iterator'Class.
The equivalent code generated uses the functions
First
and
Next exported from
List_Iterator_Interfaces
created by the instantiation of
Ada.Iterator_Interfaces
with the actual parameters
The_List.Cursor
and
The_List.Has_Element. The code then behaves
much as if it were (see paragraph 13/3 of subclause
5.5.2
of the RM)
C: The_List.Cursor;
E: Twin;
F: Forward_Iterator'Class := The_List.Iterate;
...
C := F.First;
loop
exit when not The_List.Has_Element(C);
E := The_List.Element(C);
... -- do something to E
C := F.Next(C);
end loop;
Of course, the user does not need to know all this
in order to use the construction. Note that the functions First
and Next used here (which operate on the class
Forward_Iterator and are inherited by the
class Reversible_Iterator) are not to be confused
with the existing functions First and Next
which act on the List and Cursor
respectively. The existing functions are retained for compatibility and
for use in complex situations.
It should also be noted that the initialization of
F is legal since the result returned by Iterate
is a value of Reversible_Iterator'Class and
this is a subclass of Forward_Iterator'Class.
If we had written
for C in reverse The_List.Iterate
loop
... -- do something via cursor C
end loop;
then the notional code would have been similar but
have used the functions Last and Previous
rather than First and Next.
Another point is that the function call F.First
will deliver the very first cursor value if we had written The_List.Iterate
but the value S if we had written The_List.Iterate(S).
Remember that we are dealing with interfaces so there is nothing weird
here; the two functions Iterate return different
types in the class and these have different functions First
so the notional generated code calls different functions.
If we use the form
for E: Twin of The_List loop
... -- do something to E
end loop;
then the generated
code is essentially the same. However, since we have not explicitly mentioned
an iterator, a default one has to be used. This is given by one of several
new aspects of the type List which actually
now is
type List is tagged private
with Constant_Indexing => Constant_Reference,
Variable_Indexing => Reference,
Default_Iterator => Iterate,
Iterator_Element => Element_Type;
The aspect we need
at the moment is the one called
Default_Iterator
which as we see has the value
Iterate (this
is the one without the extra parameter). So the iterator
F
is initialized with this default value and once more we get
C: The_List.Cursor;
E: Twin;
F: Forward_Iterator'Class := The_List.Iterate;
...
The use of the other aspects will be explained in
a moment.
Lists, vectors and ordered maps and sets can be iterated
in both directions. They all have procedures Reverse_Iterate
as well as Iterate and the two new
functions Iterate return a value of Reversible_Iterator'Class.
However, it might be
recalled that the notion of iterating in either direction makes no sense
in the case of hashed maps and hashed sets. Consequently, there is no
procedure Reverse_Iterate for hashed maps
and hashed sets and there is only one new function Iterate
which (in the case of hashed maps) is
function Iterate(Container: in Map) return
Map_Iterator_Interfaces.Forward_Iterator'Class;
and we note that this function returns a value of
Forward_Iterator'Class rather than Reversible_Iterator'Class
in the case of lists, vectors, ordered maps, and ordered sets.
Naturally, we cannot
put reverse in an iterator over hashed maps and hashed sets nor
can we give a starting value. So the following are both illegal
for C in The_Hash_Map.Iterate(S) loop -- illegal
for E of reverse The_Hash_Map loop -- illegal
The above should have given the reader a fair understanding
of the mechanisms involved in setting up the loops using the new iterator
forms. We now turn to considering the bodies of the loops, that is the
code marked "do something via cursor C"
or "do something to E".
In the Ada 2005 example
we wrote
if Is_Prime(E.P) then
Replace_Element(The_List, C, (E.P, E.Q + X));
end if;
It is somewhat tedious
having to write Replace_Element when using
a container whereas in the case of an array we might directly write
if Is_Prime(A(I).P) then
A(I).Q := A(I).Q + X;
end if;
The trouble is that
Replace_Element copies the whole new element
whereas in the array example we just update the one component. This doesn't
matter too much in a case where the components are small such as Twin
but if they were giant records it would clearly be a problem. To overcome
this Ada 2005 includes a procedure Update_Element
thus
procedure Update_Element(Container: in out List;
Position: in Cursor;
Process: not null access procedure
(Element: in out Element_Type));
To use this we have
to write a procedure Do_It say thus
procedure Do_It(E: in out Twin) is
begin
E.Q := E.Q + X;
end Do_It;
and then
if Is_Prime(E.P) then
Update_Element(The_List, C, Do_It'Access);
end if;
This works fine because
E is passed by reference and no giant copying
occurs. However, the downside is that the distinct procedure Do_It
has to be written so that the overall text is something like
declare
procedure Do_It(E: in out Twin) is
begin
E.Q := E.Q + X;
end Do_It;
begin
if Is_Prime(E.P) then
Update_Element(The_List, C, Do_It'Access);
end if;
end;
which is a bit tedious.
But of course, the
text in the body of Do_It is precisely what
we want to say. Using the historic concepts of left and right hand values,
the problem is that The_List(C).Element cannot
be used as a left hand value by writing for example
The_List(C).Element.Q := ...
The problem is overcome
in Ada 2012 using a little more magic by the introduction of generalized
reference types and various aspects. In particular we find that the containers
now include a type Reference_Type and a function
Reference which in the case of the list containers
are
type Reference_Type
(Element: not null access Element_Type) is private
with Implicit_Dereference => Element;
function Reference(Container: aliased in out List;
Position: in Cursor) return Reference_Type;
Note the aspect
Implicit_Dereference
applied to the type
Reference_Type with discriminant
Element.
There is also a type Constant_Reference_Type
and a function Constant_Reference for use
when the context demands read-only access.
The alert reader will note the inclusion of
aliased
for the parameter
Container of the function
Reference. As discussed in Section
4.2
on subprogram parameters, this ensures that the parameter is passed by
reference (it always is for tagged types anyway); it also permits us
to apply
'Access to the parameter
Container
within the function and to return that access value.
It might be helpful to say a few words about the
possible implementation of Reference and Reference_Type
although these need not really concern the user.
The important part
of the type Reference_Type is its access discriminant.
The private part might contain housekeeping stuff but we can ignore that.
So in essence it is simply a record with just one component being the
access discriminant
type Reference_Type
(E: not null access Element_Type) is null record;
and the body of the
function might be
function Reference(Container: aliased in out List;
Position: in Cursor) return Reference_Type is
begin
return (E => Container.Element(Position)'Access);
end Reference;
The rules regarding parameters with aliased
(which we gloss over) ensure that no accessibility problems should arise.
Note also that it is important that the discriminant of Reference_Type
is an access discriminant since the lifetime of the discriminant is then
just that of the return object.
Various aspects are
given with the type List which as shown earlier
now is
type List is tagged private
with Constant_Indexing => Constant_Reference,
Variable_Indexing => Reference,
Default_Iterator => Iterate,
Iterator_Element => Element_Type;
The important aspect here is
Variable_Indexing.
If this aspect is supplied then in essence an object of the type can
be used in a left hand context by invoking the function given as the
value of the aspect. In the case of
The_List
this is the function
Reference which returns
a value of type
Reference_Type. Moreover,
this reference type has a discriminant which is of
access Element_Type
and the aspect
Implicit_Dereference with value
Element and so gives direct access to the
value of type
Element.
We can now by stages
transform the raw text. So using the cursor form we can start with
for C in The_List.Iterator loop
if Is_Prime(The_List.Reference(C).Element.all.P) then
The_List.Reference(C).Element.all.Q :=
The_List.Reference(C).Element.all.Q + X;
end if;
end loop;
This is the full blooded version even down to using
all.
Using the dereferencing
with the aspect Implicit_Dereference we can
omit the mention of the discriminant Element
and the all to give
for C in The_List.Iterator loop
if Is_Prime(The_List.Reference(C).P) then
The_List.Reference(C).Q :=
The_List.Reference(C).Q + X;
end if;
end loop;
Remember that Reference
is a function with two parameters. It might be clearer to write this
without prefix notation which gives
for C in Iterator(The_List) loop
if Is_Prime(Reference(The_List, C).P) then
Reference(The_List, C).Q :=
Reference(The_List, C).Q + X;
end if;
end loop;
Now because the aspect
Variable_Indexing for the type List
has value Reference, the explicit calls of
Reference can be omitted to give
for C in The_List.Iterator loop
if Is_Prime(The_List(C).P) then
The_List(C).Q := The_List(C).Q + X;
end if;
end loop;
It should now be clear
that the cursor C is simply acting as an index
into The_List. We can compare this text with
for C in The_Array'Range loop
if Is_Prime(The_Array(C).P) then
The_Array(C).Q := The_Array(C).Q + X;
end if;
end loop;
which shows that 'Range
is analogous to .Iterator.
Finally, to convert
to the element form using E we just replace
The_List(C) by E
to give
for E of The_List loop
if Is_Prime(E.P) then
E.Q := E.Q + X;
end if;
end loop;
The reader might like to consider the transformations
in the reverse direction to see how the final succinct form transforms
to the expanded form using the various aspects. This is indeed what the
compiler has to do.
This underlying technique
which transforms the sequence of statements of the container element
iterator can be used quite generally. For example, we might not want
to iterate over the whole container but just manipulate a particular
element given by a cursor C. Rather than calling
Update_Element with another subprogram Do_Something,
we can write
The_List.Reference(C).Q := ...
or simply
The_List(C).Q := ...
Moreover, although the various aspects were introduced
into Ada 2012 primarily to simplify the use of containers they can be
used quite generally.
The reader may feel
that these new features violate the general ideas of a language with
simple building blocks. However, it should be remembered that even the
traditional form of loop such as
for Index in T range L .. U loop
... -- statements
end loop;
is really simply a
shorthand for
declare
Index: T;
begin
if L <= U then
Index := L;
loop
... -- statements
exit when Index = U;
Index := T'Succ(Index);
end loop;
end if;
end;
Without such shorthand, programming would be very
tedious and very prone to errors. The features described in this section
are simply a further step to make programming safer and simpler.
Further examples of the use of these new features
with containers will be given in Section
8.3.
The mechanisms discussed above rely on a number of
new aspects, a summary of which follows and might be found useful. It
is largely based on extracts from the RM.
Dereferencing
The following aspect may be specified for a discriminated
type T.
Implicit_Dereference
– This aspect is specified by a name that denotes an access discriminant
of the type
T.
A type with a specified
Implicit_Dereference
aspect is a
reference type.
The
Implicit_Dereference
aspect is inherited by descendants of type
T
if not overridden.
A generalized_reference denotes the object or
subprogram designated by the discriminant of the reference object.
Indexing
The following aspects may be specified for a tagged
type T.
Constant_Indexing –
This aspect is specified by a name that denotes one or more functions
declared immediately within the same declaration list in which
T
is declared. All such functions shall have at least two parameters, the
first of which is of type
T or
T'Class,
or is an access-to-constant parameter with designated type
T
or
T'Class.
Variable_Indexing –
This aspect is specified by a name that denotes one or more functions
declared immediately within the same declaration list in which
T
is declared. All such functions shall have at least two parameters, the
first of which is of type
T or
T'Class,
or is an access parameter with designated type
T
or
T'Class. All such functions shall have
a return type that is a reference type, whose reference discriminant
is of an access-to-variable type.}
These aspects are inherited by descendants of
T (including T'Class).
The aspects shall not be overridden, but the functions they denote may
be.
An
indexable container type is a tagged
type with at least one of the aspects
Constant_Indexing
or
Variable_Indexing specified.
An important difference between Constant_Indexing
and Variable_Indexing is that the functions
for variable indexing must return a reference type so that it can be
used in left hand contexts such as the destination of an assignment.
Note that, in both cases, the name can denote several overloaded functions;
this is useful, for example, with maps to allow indexing both with cursors
and with keys.
Both Constant_Indexing
and Variable_Indexing can be provided since
the constant one might be more efficient whereas the variable one is
necessary in left hand contexts. But we are not obliged to give both,
just Variable_Indexing might be enough for
some applications.
Iterating
An iterator type is a type descended from the
Forward_Iterator interface.
The following aspects may be specified for an
indexable container type T.
Default_Iterator –
This aspect is specified by a name that denotes exactly one function
declared immediately within the same declaration list in which
T
is declared, whose first parameter is of type
T
or
T'Class or an access parameter whose designated
type is type
T or
T'Class,
whose other parameters, if any, have default expressions, and whose result
type is an iterator type. This function is the
default iterator function
for
T.
Iterator_Element –
This aspect is specified by a name that denotes a subtype. This is the
default element subtype for
T.
These aspects are inherited by descendants of
type T (including T'Class).
An
iterable container type is an indexable
container type with specified
Default_Iterator
and
Iterator_Element aspects.
The Constant_Indexing
and Variable_Indexing aspects (if any) of
an iterable container type T shall denote
exactly one function with the following properties:
the result type of the function is covered
by the default element type of T or is a reference
type with an access discriminant designating a type covered by the default
element type of T;
the type of the second parameter of the
function covers the default cursor type for T;
if there are more than two parameters,
the additional parameters all have default expressions.
These functions (if any) are the
default indexing
functions for
T.
The reader might care to check that the aspects used
in the examples above match these definitions and are used correctly.
Note for example that the Default_Iterator
and Iterator_Element aspects are only needed
if we use the of form of iteration (and both are needed in that
case, giving one without the other would be foolish).
This section has largely been about the use of iterators
with loop statements. However, there is one other use of them and that
is with quantified expressions which are also new to Ada 2012. Quantified
expressions were discussed in some detail in Section
3.4
of the chapter on Expressions so all we need here is to consider a few
examples which should clarify the use of iterators.
Instead of
B := (for all K in A'Range => A(K) = 0);
which assigns true
to B if every component of the array A
has value 0, we can instead write
B := (for all E of A => E = 0);
Similarly, instead
of
B := (for some K in A'Range => A(K) = 0);
which assigns true
to B if some component of the array A
has value 0, we can instead write
B := (for some E of A => E = 0);
In the case of a multidimensional
array, instead of
B := (for all I in AA'Range(1) =>
(for all J in AA'Range(2) => AA(I, J) = 0));
we can write
B := (for all E of AA => E = 0);
which iterates over all elements of the array AA
however many dimensions it has.
We can also use these
forms with the list example. Suppose we are interested in checking whether
some element of the list has a prime component P.
We can write
B := (for some E of The_List => Is_Prime(E.P));
or perhaps
B := (for some C in The_List.Iterator =>
Is_Prime(The_List(C).P));
which uses the explicit iterator form.
© 2011, 2012, 2013 John Barnes Informatics.
Sponsored in part by: