comp.lang.ada
 help / color / mirror / Atom feed
* Subject: Active Iteration (was: How to use abstract data types)
@ 1998-05-06  0:00 adam
  1998-05-07  0:00 ` Matthew Heaney
  1998-05-08  0:00 ` Matthew Heaney
  0 siblings, 2 replies; 4+ messages in thread
From: adam @ 1998-05-06  0:00 UTC (permalink / raw)





Matthew Heaney wrote:

> Here's the idea I had for the library iterator.  The Library_Package.Test
> package exports an active iterator that I was hoping to use to iterate over
> a Test_Library.
>
> However, I can't get this code to compile!  My compiler is telling me the
> generic actual types don't match the formal discriminant types.
>
> If your compiler can compile this, let me know and I'll report a bug to
> ACT.  If this is simply an illegal Ada program, then maybe someone can
> figure out an alternative solution.
>
> The idea was to make the List_Books operation a generic procedure that
> imports an iterator type as a generic formal type, to iterate over the
> library object passed in.  I do it this way because importing an iterator
> as derived from an abstract root iterator type won't work, because formal
> derived types cannot have a known discriminant (see RM95 12.5.1 (11), a
> bummer of a paragraph).  So I just import everything as a non-tagged type
> (even though the actual type may in fact be tagged), and import the ops
> formal subprogram parameters ("implementation inheritance").
>
> But I can't get the instantiation of List_Books to compile.  Maybe you'll
> have more luck.

I haven't yet taken the time to figure out what's wrong yet.  But I
plan to, because I'm sure that I'd learn a lot about Ada 95 details by
doing so.

Anyway, it kind of surprises me that the solution involves a generic
that takes subprogram parameters.  The reason it surprises me is this:
based on what I thought OO was "supposed" to be, I expected that the
routines in Library_Package, including the ones that step through the
iterator, would be dispatching routines.  That is, at some point the
code would have to select which routine to call, i.e. perform an
indirect subroutine call; I expected this to take place through the
dispatching mechanism, rather than through a generic formal subprogram
(the Ada 83 way?).  Having to use a generic to handle something I
thought polymorphism should be able to handle is a bit disappointing
to me.

I tried another method for solving the problem.  Since my original
problem had to do with the fact that I couldn't use an abstract type
as an "out" parameter, I tried making it a pointer.  The program
listed below compiles and runs perfectly, and it uses the dispatching
mechanism for selecting the iteration routines, like it "should".  The
drawbacks I can see with this approach are: (1) it forces you to use
the allocation mechanism, bringing up all the problems with garbage
collection, dangling references, etc. (*); (2) the parameters of type
Library now have to be "access" to avoid accessibility problems; and
unfortunately, this requirement propagates, so that if I wrote another
subprogram S to take a Library parameter and call List_Books on that
library, S would have to declare the Library to be an "access"
parameter also.  This, to me, is a flaw.  (I could perhaps avoid this
by making the private part of Test_Library be a pointer to some
internal data, and then making the private part of
Test_Iterator_Object contain a copy of this pointer instead of an
access to the whole Test_Library.  Another possibility would be to
make the Library a parameter to all the other iteration routines.)

I'm not particularly happy with either solution.

(*) Note: Personally, this isn't a serious drawback for me; but my
perception is that some programmers have reasons for trying to avoid
the allocation mechanism.

                                -- Adam


===============================================================================

package Library_Package is

    type Library is abstract tagged null record;
    type Book is abstract tagged null record;

    type Iterator_Object is abstract tagged null record;
    type Iterator is access all Iterator_Object'class;

    function The_Library return Library is abstract;

    function Title (Bk : Book) return string is abstract;

    procedure Scan_For_Substring (Lib    : access Library;
                                  Iter   : out Iterator;
                                  Substr : in string) is abstract;

    function Is_Done (Iter : access Iterator_Object) return Boolean
        is abstract;

    function Get_Book (Iter : access Iterator_Object) return Book'class
        is abstract;

    procedure Advance (Iter : access Iterator_Object) is abstract;

end Library_Package;




with Library_Package;
package Test_Library_Package is

    type Test_Library is new Library_Package.Library with private;

    type Test_Book is new Library_Package.Book with private;

    type Test_Iterator_Object is new
        Library_Package.Iterator_Object with private;

    function The_Library return Test_Library;
    function Title (Bk : Test_Book) return string;
    procedure Scan_For_Substring (Lib    : access Test_Library;
                                  Iter   : out Library_Package.Iterator;
                                  Substr : in string);
    function Is_Done (Iter : access Test_Iterator_Object) return Boolean;
    function Get_Book (Iter : access Test_Iterator_Object) return
                 Library_Package.Book'class;
    procedure Advance (Iter : access Test_Iterator_Object);

private
    type String_P is access string;
    type Book_Info is record
        Title : String_P;
    end record;
    type Book_Array is array (Natural range <>) of Book_Info;

    type Test_Library is new Library_Package.Library with null record;

    type Test_Library_Acc is access all Test_Library;

    type Test_Book is new Library_Package.Book with record
        Info : Book_Info;
    end record;

    type Test_Iterator_Object is new
            Library_Package.Iterator_Object with record
        Lib           : Test_Library_Acc;
        Search_String : String_P;
        Index         : Natural;
    end record;

end Test_Library_Package;



with Ada.Strings.Fixed;
package body Test_Library_Package is

    My_Library : constant Book_Array :=
        ( (Title => new string' ("A Time To Kill")),
          (Title => new string' ("The Firm")),
          (Title => new string' ("The Pelican Brief")),
          (Title => new string' ("The Client")),
          (Title => new string' ("The Rainmaker")),
          (Title => new string' ("The Runaway Jury")) );

    function The_Library return Test_Library is
    begin
        return (null record);
    end The_Library;

    function Title (Bk : Test_Book) return string is
    begin
        return Bk.Info.Title.all;
    end Title;

    procedure Search (Iter : in out Test_Iterator_Object) is
    begin
        while Iter.Index <= My_Library'last loop
            exit when Ada.Strings.Fixed.Index
                          (My_Library (Iter.Index).Title.all,
                           Iter.Search_String.all) /= 0;
            Iter.Index := Iter.Index + 1;
        end loop;
    end Search;

    procedure Scan_For_Substring (Lib    : access Test_Library;
                                  Iter   : out Library_Package.Iterator;
                                  Substr : in string) is
        Iter_Obj : Test_Iterator_Object;
    begin
        Iter_Obj.Lib := Lib;
            -- the .Lib isn't actually used for anything in this
            -- package body, but in real life the routines below would
            -- use it
        Iter_Obj.Search_String := new string' (Substr);
        Iter_Obj.Index := My_Library'first;
        Search (Iter_Obj);
        Iter := new Test_Iterator_Object' (Iter_Obj);
    end Scan_For_Substring;

    function Is_Done (Iter : access Test_Iterator_Object) return Boolean is
    begin
        return (Iter.Index > My_Library'last);
    end Is_Done;

    function Get_Book (Iter : access Test_Iterator_Object) return
                 Library_Package.Book'class is
    begin
        return Test_Book' (Info => My_Library (Iter.Index));
    end Get_Book;

    procedure Advance (Iter : access Test_Iterator_Object) is
    begin
        Iter.Index := Iter.Index + 1;
        Search (Iter.all);
    end Advance;

end Test_Library_Package;



with Library_Package;
package List_Package is

    procedure List_Books (Lib    : access Library_Package.Library'class;
                          Substr : in string);

end List_Package;


with Text_IO;
package body List_Package is

    procedure List_Books (Lib    : access Library_Package.Library'class;
                          Substr : in string) is
        Iter : Library_Package.Iterator;
    begin
        Library_Package.Scan_For_Substring (Lib, Iter, Substr);
        while not Library_Package.Is_Done (Iter) loop
            declare
                Bk : Library_Package.Book'class :=
                         Library_Package.Get_Book (Iter);
            begin
                Text_IO.Put_Line (Library_Package.Title (Bk));
            end;
            Library_Package.Advance (Iter);
        end loop;
    end List_Books;

end List_Package;



with Test_Library_Package;
with List_Package;
procedure Libtest3 is
    The_Lib : aliased Test_Library_Package.Test_Library;
begin
    The_Lib := Test_Library_Package.The_Library;
    List_Package.List_Books (The_Lib'access, "m");
end Libtest3;


-----== Posted via Deja News, The Leader in Internet Discussion ==-----
http://www.dejanews.com/   Now offering spam-free web-based newsreading




^ permalink raw reply	[flat|nested] 4+ messages in thread

* Re: Subject: Active Iteration (was: How to use abstract data types)
  1998-05-06  0:00 Subject: Active Iteration (was: How to use abstract data types) adam
@ 1998-05-07  0:00 ` Matthew Heaney
  1998-05-08  0:00 ` Matthew Heaney
  1 sibling, 0 replies; 4+ messages in thread
From: Matthew Heaney @ 1998-05-07  0:00 UTC (permalink / raw)



(start of quote)
Matthew Heaney wrote:

> Here's the idea I had for the library iterator.  The Library_Package.Test
> package exports an active iterator that I was hoping to use to iterate over
> a Test_Library.
>
> However, I can't get this code to compile!  My compiler is telling me the
> generic actual types don't match the formal discriminant types.
>
> If your compiler can compile this, let me know and I'll report a bug to
> ACT.  If this is simply an illegal Ada program, then maybe someone can
> figure out an alternative solution.
(end of quote)

I submitted a bug report to ACT re GNAT v3.10p, and Robert sent me a note
to let me know that the program does compile using "the current version of
GNAT."




^ permalink raw reply	[flat|nested] 4+ messages in thread

* Re: Subject: Active Iteration (was: How to use abstract data types)
  1998-05-06  0:00 Subject: Active Iteration (was: How to use abstract data types) adam
  1998-05-07  0:00 ` Matthew Heaney
@ 1998-05-08  0:00 ` Matthew Heaney
  1998-05-08  0:00   ` Brian Rogoff
  1 sibling, 1 reply; 4+ messages in thread
From: Matthew Heaney @ 1998-05-08  0:00 UTC (permalink / raw)



In article <6iq9cl$i3t$1@nnrp1.dejanews.com>, adam@irvine.com wrote:

(start of quote)
Anyway, it kind of surprises me that the solution involves a generic
that takes subprogram parameters.  The reason it surprises me is this:
based on what I thought OO was "supposed" to be, I expected that the
routines in Library_Package, including the ones that step through the
iterator, would be dispatching routines.  That is, at some point the
code would have to select which routine to call, i.e. perform an
indirect subroutine call; I expected this to take place through the
dispatching mechanism, rather than through a generic formal subprogram
(the Ada 83 way?).  Having to use a generic to handle something I
thought polymorphism should be able to handle is a bit disappointing
to me.
(end of quote)

See point 7 below.  I was trying to avoid heap allocation.  The code
included below is completely polymorphic, doing what OO is "supposed" to be
buying you.

My other reason to the generic approach is to try an convince people that
you don't always need completely dynamic behavior.  There are times where
you know up front what the specific types are, and so the generic approach
works just great.  This isn't the "Ada 83" way, it's just the "Ada" way.

In pure OO languages (whatever that means), you create an abstract
superclass  from which other types subclass, to define the interface of the
class.  But this technique isn't strictly required in Ada 95 - it's only
required when you need dynamic behavior.

The reason is that I can import a type and a set of operations another way
in Ada, via generic formal subprogram parameters.  I don't need to define
the interface of a type by declaring a superclass.  This is exactly the
approach I took with my earlier implementation of List_Books: I import the
iterator via generic formals.  Why do I need to import a type derived from
a root iterator, unless I need to dispatch on its operations?  

Use static binding when you need static binding, and use dynamic binding
when you need dynamic binding.  Don't think that importing a formal derived
type is somehow "superior" to the traditional way.  It's its complement,
not replacement.

As a matter of fact, importing a type using generic formal subprogram
parameters has a name, "implementation inheritance."  When you need to
import in interface, the use interface inheritance (derivation from a
parent tagged type).  When you need to import an implementation, then use
implementation inheritence.

This is the kind of thing I did in the ACL (Ada Components Library).  You
import an implementation of a data structure using implementation
inheritance, and no type derivation is required thank you very much. 
Something like

generic
   type Stack_Item is private;
...
   type Stack_Rep is private;

   with function Do_Push 
     (Item : in Stack_Item; 
      Impl : in out Stack_Rep) is <>;

   with function Do_Pop (Impl : in out Stack_Rep) is <>;
...
package Stacks is 

   type Stack_Type is private;

   procedure Push 
     (Item : in        Stack_Item;
      Stack : in out Stack_Type);
...
private

   type Stack_Type is
      record
          Rep : Stack_Rep;
      end record;

end;


The stack imports an implementation via implementation inheritance.  So the
stack and queue and ring and ... are all very simple - more or less just
call-throughs to the rep type.  The beauty of this approach is that I can
wrote ONE unbounded (say) implementation, that I can plug into all my data
structures.  Beaucoup code reuse, with just a few simple modules that the
client can mix and match as he pleases.

(start of quote)
I tried another method for solving the problem.  Since my original
problem had to do with the fact that I couldn't use an abstract type
as an "out" parameter, I tried making it a pointer.  The program
listed below compiles and runs perfectly, and it uses the dispatching
mechanism for selecting the iteration routines, like it "should".  The
drawbacks I can see with this approach are: (1) it forces you to use
the allocation mechanism, bringing up all the problems with garbage
collection, dangling references, etc. (*); (2) the parameters of type
Library now have to be "access" to avoid accessibility problems; and
unfortunately, this requirement propagates, so that if I wrote another
subprogram S to take a Library parameter and call List_Books on that
library, S would have to declare the Library to be an "access"
parameter also.  This, to me, is a flaw.  (I could perhaps avoid this
by making the private part of Test_Library be a pointer to some
internal data, and then making the private part of
Test_Iterator_Object contain a copy of this pointer instead of an
access to the whole Test_Library.  Another possibility would be to
make the Library a parameter to all the other iteration routines.)

I'm not particularly happy with either solution.
(end of quote)

See the code provided below.

(start of quote)
(*) Note: Personally, this isn't a serious drawback for me; but my
perception is that some programmers have reasons for trying to avoid
the allocation mechanism.
(end of quote)

I too try to avoid heap allocation.  But here I relented, and used heap to
get around a, um, "feature" of Ada (again, see point 7).

Hope this helps,
Matt

P.S. Here are some coding idioms you may want to start following:

1) Packages that export an ADT should be named the plural of the ADT (which
should of course be singular).  Don't use that old <something>_Package
idiom either; the existence of children means _Package adds too much
verbosity to the expanded name of a library unit.  

Here, we have the packages:

Libraries
Libraries.Test
Libraries.List

2) Name the abstract root of type hierary Root_<something>, ie

   type Root_Library is abstract tagged ...;
   type Root_Book is abstract tagged ...;
   type Root_Iterator is abstract tagged ...;


3) The type hierarchy should follow the package hierarchy, ie

package Libraries exports
   type Root_Library
   type Root_Book
   type Root_Iterator

package Libraries.Test exports
   type Test_Library
   type Test_Book
   type Test_Iterator


4) Constructors are functions in Ada.  That means to create a new iterator
object on the heap, you don't return it as a procedure out param.  It
should be a function that returns the type, ie

   function New_Iterator 
     (Lib : access Root_Library) return Iterator_Access is abstract;

   function New_Iterator 
      (Lib : access Test_Library) return Iterator_Access;

5) Active iterators are limited private, and take the structure to iterator
over as an access parameter.  Whatever you do, DO NOT make the iterator
non-limited, with an access type component that designates the structure;
you WILL have problems with dangling pointers if you do it that way.

   type Root_Iterator is abstract tagged limited null record;

   type Test_Iterator (Lib : access Test_Library'Class) is
      new Root_Iterator with private;


6) There are idioms for storage allocation and deallocation more
sophisticated than I've shown here, but do take note of what I did:

6a) Make the Iterator_Access type have a storage size of 0.  This means you
can't use it to allocate any objects.  This is GOOD, because it allows
derived types to implement their own allocation schemes, and removes any
ambiguity about when you should call unchecked_deallocate Iterator_Access
(never).

6b) Provide a dispatching deallocation operation, to return the memory back
to the pool managed by the package that exports the derived type:

  procedure Deallocate (Iter : access Root_Iterator) is abstract;

  procedure Deallocate (Iter : access Test_Iterator);

6c) Provide a class-wide operation Free, that calls the dispatching
deallocate, and sets the access object passed in to null.

(Credit for these memory management ideas goes to Bob Duff.  Or was it Bob
Eachus?  I owe them both a huge debt for teaching me most of what I know
about Ada 95.)


7) The need to put the iterator on the heap points out a flaw (gasp!) in
Ada 95, namely, that we don't have true constructors.

The traditional way to "construct" an object is to call a function
(returning a value of the type) in the declarative region, ie

declare
   O : T := To_T (A, B, C);
begin

In this sense, an Ada function is really doing double duty: it's of course
a regular function that you can call in the executable region, but because
you can call it in the declarative region, it's kinda sorta a constructor
too.  That's the justification for not allowing you to do this:

declare
   O : T (A, B, C);  -- constructor for T
begin

(And no, I'm not talking about that kludge some people advocate, about
declaring the type with discriminants that you can parse in an Initialize
operation.)

The problem is that Ada confuses two very different things: binding and
assignment.  It uses the same operator, ":=", for both.  For non-limited
types this isn't so much of an issue, because you can construct an object
in the declarative region by calling a function.

But what about limited types?  By definition, a limited type doesn't come
with assignment.  But by coupling assignment and binding, a limited type
can't be bound to a value during its elaboration, ie

declare
   F : File_Type;
begin
   <state of F is undefined>
   Open (F, "file.dat");

This is a real bummer, in my so humble opinion.  What I would prefer is
something like

declare
   F : File_Type'Open ("file.dat");
begin
   <Ahhh, state of F is defined at ALL times...>

I've advocated using the tic mark to allow you to invoke a constructor
operation.  So now we can properly bind a limited object to a value during
its elaboration, even though the object still doesn't have assignment.

This also means we would be able to have a limited type that is indefinate.

The problem with our iterator is that we can't do this:

   function New_Iterator 
     (Lib : access Root_Library) return Root_Iterator'Class is abstract;

   function New_Iterator 
     (Lib : access Test_Library) return Root_Iterator'Class;

procedure List_Books (Lib : access Root_Library'Class) is

   Iter : Root_Iterator'Class := New_Iterator (Lib);
begin

This dispatching constructor (or function call, if you prefer) is illegal,
because assignment isn't available for iterators, because that type is
limited.  

I feel it should be legal, because construction of an object (binding an
object to a value) isn't the same as assignment.

I propose amending the language ("extending the syntax" for Team-Ada
readers) to allow this sort of thing:

procedure List_Books (Lib : access Root_Library'Class) is
   
   Iter : Root_Iterator'Class'New_Iterator (Lib);
begin

This is an example of an indefinate type - Root_Iterator'Class (remember,
all classwide types are indefinate) - that is also limited.  For an
indefinate type, I need to give it some initial value, so I need to invoke
a constructor to do that.  But I can't for limited types.  Major league
bummer.

Ironically, I can kinda sorta solve the problem, in a roundabout way: by
putting the iterator on the heap!  This seems completely wrong to me,
because Ada was designed do you don't have to use the heap to manipulate
unconstrained objects.  Unconstrained objects can be put on the stack, and
they get reclaimed automatically when the stack is popped.  For example,

declare
   S : String := Name (F);
begin

This sort of thing is what makes Ada so great for doing real-time and
safety-critical systems: no memory management to worry about, because you
can use the stack as a sort of tempory heap.

I can't use the stack to declare my iterator object (whose type is
unconstrained), because proper construction of the object during its
elaboration on the stack is prevented, because construction went away with
assignment (because the type is limited).

Construction should not have gone away too for limited types.  It's just a
"feature" of the language that I can declare my 8 byte iterator on the
heap, but I can't put the same 8 bytes on the stack.  There is no good
reason for this, I do say so myself!

So we work around the problem: allocate the iterator on the heap, and then
deallocate the iterator prior to leaving the frame:

procedure List_Books (Lib : access Root_Iterator'Class) is

   Iter : Iterator_Access := New_Iterator (Lib);
begin
   while not Is_Done (Iter) loop
         ... Get_Book (Iter) ...
         Advance (Iter);
   end loop;

   Free (Iter);
end List_Books;

8) Don't have a primitive operation of a tagged type return a specific type, ie

   function The_Library return Root_Library is abstract;

No, no, no!  This will make the type "go abstract" whenever a derivation
occurs, even if the type isn't extended.  For example, we often use the
technique of "transitivity of visibility" to make the type name and
operations directly visible in a certain scope, ie

package P is

   package Q is new GQ (...);

   type T is new Q.T with null record;

end P;

Oops!  This is illegal, because P.T "goes abstract," because it has a
primitive operation like this:

generic
   ...
package GQ is

   type T is tagged ...;

   function Op return T;

end;

All the innocent writer of P wanted to do was make it easy for clients to
refer to P.T, instead in P.Q.T.

The solution is to either

8a) Declare the operations in a nested (or child) package, so that they
aren't primitive, ie

generic
   ...
package GQ is

   type T is tagged ...;
  
   package Constructors is

      funtion To_T (A, B, C, : ...) return T;

   end;

end GQ;


8b) Declare the functions to return a class-wide type, ie

generic
  ...
package GQ is

   type T is tagged ...;

   function T (A, B, C : ...) return T'Class;

end;

Now all is well, and you can use transitivity of visibility with impunity.

I have other idioms and guidelines (like, don't use _Type to name a
type...), but I'll save those for another type, er, I mean time...


-- STX
with Text_IO;
package body Libraries.List is

   procedure List_Books 
     (Lib    : access Root_Library'Class;
      Substr : in     String) is

      Iter : Iterator_Access := New_Iterator (Lib);
    begin
        Scan_For_Substring (Iter, Substr);

        while not Is_Done (Iter) loop
            declare
               Bk : Root_Book'Class := 
                 Get_Book (Iter);
            begin
                Text_IO.Put_Line (Title (Bk));
            end;
            Advance (Iter);
        end loop;
        
        Free (Iter);

    end List_Books;

end Libraries.List;
package Libraries.List is

   procedure List_Books
     (Lib    : access Root_Library'Class;
      Substr : in     String);

end Libraries.List;
with Ada.Unchecked_Deallocation;
with Ada.Strings.Fixed;

package body Libraries.Test is

    function Title (Bk : Test_Book) return string is
    begin
        return Bk.Info.Title.all;
    end Title;

    procedure Search (Iter : in out Test_Iterator) is

       Search_String : String renames Iter.Search_String.all;

       use Ada.Strings.Fixed;

    begin
        while Iter.Index <= Iter.Lib.Books'last loop

           declare
              Lib : Test_Library renames Iter.Lib.all;

              Book : Test_Book renames Lib.Books (Iter.Index);

              Title : String renames Book.Info.Title.all;
           begin
              exit when Index (Title, Search_String) /= 0;
           end;

           Iter.Index := Iter.Index + 1;

        end loop;
    end Search;


    procedure Scan_For_Substring
      (Iter   : access Test_Iterator;
       Substr : in     string) is
    begin
        Iter.Search_String := new string' (Substr);
        Iter.Index := Iter.Lib.Books'First;
        Search (Iter.all);
    end Scan_For_Substring;


    function Is_Done
      (Iter : access Test_Iterator) return Boolean is
    begin
       return Iter.Index > Iter.Lib.Books'Last;
    end Is_Done;


    function Get_Book
      (Iter : access Test_Iterator)
       return Root_Book'Class is
    begin
       return Iter.Lib.Books (Iter.Index);
    end Get_Book;


    procedure Advance (Iter : access Test_Iterator) is
    begin
        Iter.Index := Iter.Index + 1;
        Search (Iter.all);
    end Advance;


    type Test_Iterator_Access is
       access all Test_Iterator;

    procedure Free is
      new Ada.Unchecked_Deallocation (Test_Iterator, Test_Iterator_Access);


    function New_Iterator
      (Lib : access Test_Library) return Iterator_Access is

       Iter : constant Test_Iterator_Access :=
         new Test_Iterator (Lib);
    begin
       return Iterator_Access (Iter);
    end;

    procedure Deallocate
      (Iter : access Test_Iterator) is

       IA : Test_Iterator_Access :=
         Test_Iterator_Access (Iter);
    begin
       Free (IA);
    end;

end Libraries.Test;
package Libraries.Test is

    type Test_Library is new Root_Library with private;

    type Test_Book is new Root_Book with private;

    type Test_Iterator (Lib : access Test_Library'Class) is
      new Root_Iterator with private;

    function Title (Bk : Test_Book) return string;

    function New_Iterator
      (Lib : access Test_Library) return Iterator_Access;

    procedure Scan_For_Substring
      (Iter   : access Test_Iterator;
       Substr : in     String);

    function Is_Done
      (Iter : access Test_Iterator) return Boolean;

    function Get_Book
      (Iter : access Test_Iterator) return Root_Book'class;

    procedure Advance
      (Iter : access Test_Iterator);

    procedure Deallocate
      (Iter : access Test_Iterator);

private

    type String_P is access string;

    type Book_Info is record
        Title : String_P;
    end record;

    type Test_Book is
      new Root_Book with record
        Info : Book_Info;
      end record;


    type Book_Array is array (Natural range <>) of Test_Book;

    type Test_Library is
      new Root_Library with record
         Books : Book_Array (1 .. 6) :=
        ( (Info => (Title => new string' ("A Time To Kill"))),
          (Info => (Title => new string' ("The Firm"))),
          (Info => (Title => new string' ("The Pelican Brief"))),
          (Info => (Title => new string' ("The Client"))),
          (Info => (Title => new string' ("The Rainmaker"))),
          (Info => (Title => new string' ("The Runaway Jury"))) );
      end record;


    type Test_Iterator (Lib : access Test_Library'Class) is
      new Root_Iterator with record
        Search_String : String_P;
        Index         : Natural;
    end record;

end Libraries.Test;
package body Libraries is

    procedure Free (Iter : in out Iterator_Access) is
    begin
       if Iter = null then
          return;
       end if;

       Deallocate (Iter);

       Iter := null;
    end Free;

end Libraries;
package Libraries is

   type Root_Library is abstract tagged null record;

   type Root_Book is abstract tagged null record;


   type Root_Iterator is abstract tagged limited null record;

   type Iterator_Access is access all Root_Iterator'Class;
   for Iterator_Access'Storage_Size use 0;


   function Title
     (Bk : Root_Book) return string is abstract;


   function New_Iterator
     (Library : access Root_Library) return Iterator_Access is abstract;


   procedure Scan_For_Substring
     (Iter   : access Root_Iterator;
      Substr : in     String) is abstract;

    function Is_Done
      (Iter : access Root_Iterator) return Boolean is abstract;

    function Get_Book
      (Iter : access Root_Iterator) return Root_Book'class is abstract;

    procedure Advance
      (Iter : access Root_Iterator) is abstract;


   procedure Deallocate (Iter : access Root_Iterator) is abstract;


   procedure Free (Iter : in out Iterator_Access);


end Libraries;
with Libraries.Test;  use Libraries.Test;
with Libraries.List;  use Libraries.List;

procedure Libtest3 is
    The_Lib : aliased Test_Library;
begin
    List_Books (The_Lib'access, "m");
end Libtest3;




^ permalink raw reply	[flat|nested] 4+ messages in thread

* Re: Subject: Active Iteration (was: How to use abstract data types)
  1998-05-08  0:00 ` Matthew Heaney
@ 1998-05-08  0:00   ` Brian Rogoff
  0 siblings, 0 replies; 4+ messages in thread
From: Brian Rogoff @ 1998-05-08  0:00 UTC (permalink / raw)



On Fri, 8 May 1998, Matthew Heaney wrote:
> In article <6iq9cl$i3t$1@nnrp1.dejanews.com>, adam@irvine.com wrote:
> (start of quote)
> Anyway, it kind of surprises me that the solution involves a generic
> that takes subprogram parameters.  The reason it surprises me is this:
> based on what I thought OO was "supposed" to be, I expected that the
> routines in Library_Package, including the ones that step through the
> iterator, would be dispatching routines.  That is, at some point the
> code would have to select which routine to call, i.e. perform an
> indirect subroutine call; I expected this to take place through the
> dispatching mechanism, rather than through a generic formal subprogram
> (the Ada 83 way?).  Having to use a generic to handle something I
> thought polymorphism should be able to handle is a bit disappointing
> to me.
> (end of quote)
> 
> ... snip ...

> My other reason to the generic approach is to try an convince people that
> you don't always need completely dynamic behavior.  There are times where
> you know up front what the specific types are, and so the generic approach
> works just great.  This isn't the "Ada 83" way, it's just the "Ada" way.

A laudable approach IMO. Another approach involving genericity and not
possible in Ada 83 involves the use of (null bodied) generic signature 
packages to abstract the iterator interface. This solves one of the "Ada 
nasties" mentioned by J. Bishop in her article on implementing iterator 
abstractions (I forget the ref, some IEEE journal of around 1990) using
Ada 83 generics, the nasty being that it wasn't possible to have many
implementations for a given generic interface.

The other Ada problem of course involved procedure parameters and is
partially fixed by procedure access types (and fully fixed in GNAT). 

-- Brian





^ permalink raw reply	[flat|nested] 4+ messages in thread

end of thread, other threads:[~1998-05-08  0:00 UTC | newest]

Thread overview: 4+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
1998-05-06  0:00 Subject: Active Iteration (was: How to use abstract data types) adam
1998-05-07  0:00 ` Matthew Heaney
1998-05-08  0:00 ` Matthew Heaney
1998-05-08  0:00   ` Brian Rogoff

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox