comp.lang.ada
 help / color / mirror / Atom feed
* How to Use Abstract Data Types
@ 1998-04-22  0:00 adam
  1998-04-23  0:00 ` Jacob Sparre Andersen
  1998-04-30  0:00 ` Robert I. Eachus
  0 siblings, 2 replies; 10+ messages in thread
From: adam @ 1998-04-22  0:00 UTC (permalink / raw)



I'm just starting to use some of the advanced OO features of Ada 95,
and I've run into a situation that I don't know what the best solution
is.  Or maybe I'm completely confused about something.

Here's an example of what I'm trying to accomplish.  I'd like to
define an abstract data type, Library, that denotes a collection of
books.  Since this collection could be implemented in several
ways---say, as a flat file, or a file organized as a tree, or perhaps
not a file at all but rather by querying some other site on the
Internet---the type would be an abstract tagged type, and the package
that declares it would declare abstract procedures to deal with it.
I'd assume that the type Book, which represents one book, would be an
abstract type, also.

One of the functions I would want is one to search for all books whose
title matches a certain regular expression.  My usual idiom for this
sort of scan is to declare four subprograms---something like
Start_Scan (which gets things started but doesn't return any items),
More_Items (which returns TRUE if there are more items to return),
Next_Item (which returns the next one), and Close_Scan (to clean up).
This idiom also involves declaring a type to hold "current item"
information needed by the scan routines; an object of this type is set
up by Start_Scan, More_Items tests the object, and Next_Item modifies
it.  I strongly prefer this over having the current scan information
"hidden" globally inside the package body, since it means there's no
problem for two parts of the calling program to conduct two scans in
parallel.

If I define a record to hold the current scan information, it would
also have to be abstract (right?), since its contents would vary
depending on the implementation.  That is, for libraries implemented
as a tree file, it might contain a stack of node addresses, or
something like that.

So say my package spec looks like this:

    package Library_Package is

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

        type Scan_Info is abstract tagged null record;

        ... procedure(s) to set up a new Library object

        procedure Scan_By_Title (Lib            : in Library;
                                 Reg_Expression : in String;
                                 Scan           : out Scan_Info;
                                 RE_Error       : out Boolean);
        function More_Books (Scan : Scan_Info) return Boolean;
        procedure Next_Book (Scan     : in out Scan_Info;
                             Bk       : out Book);
        procedure Close_Scan (Scan : in out Scan_Info);

        ... etc.

    end Library_Package;

For Scan_By_Title, RE_Error would be set to TRUE if Reg_Expression is
ill-formed.

But it looks like this isn't going to work.  If I were to write a
procedure that lists all the books in a library whose titles match,
I'd want to be able to write:

    procedure List_Books_With_Matching_Titles
                  (Lib           : in Library'Class;
                   Title_Pattern : in String) is
        ... declarations
    begin
        Scan_By_Title (Lib, Title_Pattern, List_Scan, Error);
        if Error then
            Insult_The_User;
            return;
        end if;
        while More_Books (List_Scan) loop
            Next_Book (List_Scan, The_Book_To_List);
            List_Book (The_Book_To_List);
        end loop;
        Close_Scan (List_Scan);
    end List_Books_With_Matching_Titles;

But I don't see how this can be done, since I can't declare List_Scan.
I can't declare it as Library_Package.Scan_Info since that is an
abstract type, and I can't declare it as
Library_Package.Scan_Info'Class since I need an initializer.  I guess
I could declare it as Scan_Info'Class if I turned Scan_By_Title into a
function, but then I'd have to find some other way to take care of the
RE_Error output (in this particular case, I could use an exception,
but imagine a case where I want to return something that isn't a
simple success/failure boolean).  I also don't see how to declare
The_Book_To_List, and I can't see turning Next_Book into a function
since Scan has to be an "in out" parameter.

Am I missing something trivial here?

What is the cleanest way to accomplish what I'm trying to do?  This
looks like such a typical use of polymorphism that I'd be surprised if
there were no intuitive way to do it.

                                -- thanks, Adam

-----== 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] 10+ messages in thread

* Re: How to Use Abstract Data Types
  1998-04-22  0:00 adam
@ 1998-04-23  0:00 ` Jacob Sparre Andersen
  1998-04-30  0:00 ` Robert I. Eachus
  1 sibling, 0 replies; 10+ messages in thread
From: Jacob Sparre Andersen @ 1998-04-23  0:00 UTC (permalink / raw)


[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #1: Type: text/plain, Size: 10657 bytes --]


------------------------------------------------------------------------------
--  Jacob:
--
--  This message should be ready to compile.
--
--  My reply is directed only to the problem Adam presented. There are no
--  general guidelines here (that I am aware of).
--
--  I know that my choice of coding style can be (and has been) discussed,
--  but lets keep it separate from the library/OO ADT business.

------------------------------------------------------------------------------
--  Adam (adam@irvine.com):
--
--  I'm just starting to use some of the advanced OO features of Ada 95,
--  and I've run into a situation that I don't know what the best solution
--  is.  Or maybe I'm completely confused about something.
--
--  Here's an example of what I'm trying to accomplish.  I'd like to
--  define an abstract data type, Library, that denotes a collection of
--  books.  Since this collection could be implemented in several
--  ways---say, as a flat file, or a file organized as a tree, or perhaps
--  not a file at all but rather by querying some other site on the
--  Internet---the type would be an abstract tagged type, and the package
--  that declares it would declare abstract procedures to deal with it.
--  I'd assume that the type Book, which represents one book, would be an
--  abstract type, also.

------------------------------------------------------------------------------
--  Jacob:
--
--  Here is how I see the problem at hand:
--
--     You have books of various kinds. The common features of all kinds
--     of all kinds of books are collected in type Abstract_Book.Object.
--
--     A library is a collection of books. You can walk through a library
--     looking for a book, add books to a library, remove books from a library
--     (even though you shouldn't), read books in a library, and you can
--     borrow books from and return them to a library.
--
--     Some libraries even have indexes to the library so you can look up
--     books by their title, author, or subject.

------------------------------------------------------------------------------
--  Abstract book:

with Libraries;
with String_Lists;

package Abstract_Book is

   type Object is abstract tagged private;
   subtype Class is Object'Class;
   type Reference is access all Class;

   function Title (Book : in Abstract_Book.Object) return String is abstract;

   function Authors (Book : in Abstract_Book.Object) return String_Lists.List
     is abstract;

   function Subject (Book : in Abstract_Book.Object)
     return Libraries.Subject_Code is abstract;

private

   --  I have chosen to keep the base information about the books out of
   --  Abstract_Book.Object in case we are going to work with "books" where
   --  the information can be found through some other means.

   type Object is abstract tagged null record;

end Abstract_Book;

------------------------------------------------------------------------------
--  Abstract library:

with Abstract_Book;
with Libraries;

package Abstract_Library is

   type Object is abstract tagged private;
   subtype Class is Object'Class;
   type Reference is access all Class;

   Full      : exception;
   Not_Found : exception;

   procedure Add (To   : in out Abstract_Library.Object;
                  Book : in     Abstract_Book.Class;
                  ID   :    out Libraries.Book_ID) is abstract;

   procedure Remove (From : in out Abstract_Library.Object;
                     ID      : in     Libraries.Book_ID;
                     Book    :    out Abstract_Book.Class) is abstract;

   procedure Remove (From : in out Abstract_Library.Object;
                     Book : in     Libraries.Book_ID) is abstract;

   procedure Read_Book (Library : in     Abstract_Library.Object;
                        ID      : in     Libraries.Book_ID;
                        Book    :    out Abstract_Book.Class) is abstract;

   procedure Borrow (From : in out Abstract_Library.Object;
                     ID   : in     Libraries.Book_ID;
                     Book :    out Abstract_Book.Class) is abstract;

   procedure Return_Book (Library : in out Abstract_Library.Object;
                          Book    : in     Abstract_Book.Class) is abstract;

   type Look_At_Reference is
     access procedure (Book : in     Abstract_Book.Class;
                       ID   : in     Libraries.Book_ID;
                       Stop :    out Boolean);

   procedure Walk_Through (Library    : in     Abstract_Library.Object;
                           Look_At    : in     Look_At_Reference;
                           Terminated :    out Boolean);

   type Process_Reference is
     access procedure (Book : in out Abstract_Book.Class;
                       Stop :    out Boolean);

   procedure Walk_Through (Library    : in     Abstract_Library.Object;
                           Process    : in     Process_Reference;
                           Terminated :    out Boolean);

private

   type Object is abstract tagged null record;

end Abstract_Library;

------------------------------------------------------------------------------
--  Abstract book query:

with Libraries;

package Abstract_Book_Query is

   type Object is abstract tagged private;
   subtype Class is Object'Class;
   type Reference is access all Class;

   --  The initial state of a query should always be before the first result
   --  from the query.
   --
   --  Current will fail if called before Next has been called.

   procedure Current (Query : in     Abstract_Book_Query.Object;
                      Book  :    out Libraries.Book_ID) is abstract;

   procedure Next (Query : in out Abstract_Book_Query.Object;
                   Book  :    out Libraries.Book_ID) is abstract;

   function End_Of_Query (Query : in Abstract_Book_Query.Object)
     return Boolean is abstract;

private

   type Object is abstract tagged null record;

end Abstract_Book_Query;

------------------------------------------------------------------------------
--  Abstract indexed library:

with Abstract_Book_Query;
with Abstract_Library;
with Libraries;
with Pattern_Matching;

package Abstract_Indexed_Library is

   type Object is abstract new Abstract_Library.Object with private;
   subtype Class is Object'Class;
   type Reference is access all Class;

   --  Here I declare *abstract* constructors for some book queries.
   --  You will have to declare a non-abstract descendant of
   --  Abstract_Book_Query.Object to implement the constructors.

   function Search_For_Title (Library : in Abstract_Indexed_Library.Object;
                              Pattern : in Pattern_Matching.Pattern)
     return Abstract_Book_Query.Class is abstract;

   function Search_For_Author (Library : in Abstract_Indexed_Library.Object;
                               Pattern : in Pattern_Matching.Pattern)
     return Abstract_Book_Query.Class is abstract;

   function Search_For_Subject (Library : in Abstract_Indexed_Library.Object;
                                Subject : in Libraries.Subject_Code)
     return Abstract_Book_Query.Class is abstract;

private

   type Object is abstract new Abstract_Library.Object with null record;

end Abstract_Indexed_Library;

------------------------------------------------------------------------------
--  Adam:
--
--  One of the functions I would want is one to search for all books whose
--  title matches a certain regular expression.
--
--  [cut]
--
--  If I were to write a procedure that lists all the books in a library whose
--  titles match, I'd want to be able to write:

    procedure List_Books_With_Matching_Titles
                  (Lib           : in Library'Class;
                   Title_Pattern : in String) is
        --  declarations
    begin
        Scan_By_Title (Lib, Title_Pattern, List_Scan, Error);
        if Error then
            Insult_The_User;
            return;
        end if;
        while More_Books (List_Scan) loop
            Next_Book (List_Scan, The_Book_To_List);
            List_Book (The_Book_To_List);
        end loop;
        Close_Scan (List_Scan);
    end List_Books_With_Matching_Titles;

--  But I don't see how this can be done, since I can't declare List_Scan.
--  I can't declare it as Library_Package.Scan_Info since that is an
--  abstract type, and I can't declare it as Library_Package.Scan_Info'Class
--  since I need an initializer.  I guess I could declare it as
--  Scan_Info'Class if I turned Scan_By_Title into a function, but then I'd
--  have to find some other way to take care of the RE_Error output (in this
--  particular case, I could use an exception, but imagine a case where I want
--  to return something that isn't a simple success/failure boolean).  I also
--  don't see how to declare The_Book_To_List, and I can't see turning
--  Next_Book into a function since Scan has to be an "in out" parameter.

------------------------------------------------------------------------------
--  Jacob:
--
--  I rewrite your procedure List_Books_With_Matching_Titles with some minor
--  changes:

    with Abstract_Book_Query;
    with Abstract_Indexed_Library;
    with Libraries;
    with Pattern_Matching;

    procedure List_Books (Library : in Abstract_Indexed_Library.Class;
                          Title   : in Pattern_Matching.Pattern) is

       use Abstract_Book_Query;
       use Abstract_Indexed_Library;

       Query : Abstract_Book_Query.Reference;
       Book  : Libraries.Book_ID;

    begin
       Query := new Abstract_Book_Query.Class' (Search_For_Title
                                                  (Library => Library,
                                                   Pattern => Title));

       while not End_Of_Query (Query.all) loop
          Next (Query => Query.all,
                Book  => Book);
          --List_Book (Book);
       end loop;
    end List_Books;

------------------------------------------------------------------------------
--  Various stuff to get things to compile:

package Libraries is
  type Subject_Code is new String (1 .. 6);
  subtype Book_ID is Natural;
end Libraries;

package Pattern_Matching is
   type Pattern is new String;
end Pattern_Matching;

package String_Lists is
   type List is new String;
end String_Lists;

--  Greetings,
--
--  Jacob
--
----------------------------------------------------------------------------
--  Jacob Sparre Andersen     --  E-mail: Jacob.Sparre.Andersen@risoe.dk  --
--  National Laboratory Ris�  --  Phone.: (+45) 46 77 51 23               --
--  Systems Analysis          --  Fax...: (+45) 46 77 51 99               --
----------------------------------------------------------------------------




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

* Re: How to Use Abstract Data Types
@ 1998-04-30  0:00 adam
  1998-05-06  0:00 ` Robert I. Eachus
  0 siblings, 1 reply; 10+ messages in thread
From: adam @ 1998-04-30  0:00 UTC (permalink / raw)



Robert Eachus wrote:

>  > Am I missing something trivial here?
>
> -- Yes, but you can be forgiven because it is not trivial in many OO
> -- langauges.  There are cases where you have to use access parameters
> -- and all that to duplicate the normal way of doing iterators in
> -- other languages.  In Ada, you are always better off making
> -- iterators objects, but in Ada 95 the much cleaner way of doing
> -- iterators is to use instances of generic packages as the iterator
> -- objects.  Sounds compilicated, but it isn't.  First, we will
> -- realize that Books and libraries are separate abstractions:
>
> package Books is
>
>    type Book is ...;
>    function Title(B: Book) return String;
>    ...
> end Books;
>
> with Books
> package Libraries is
>
>    type Library is abstract tagged null record;
>
>    -- various abstract operations on Libraries.
>
>    generic
>       type Some_Library is new Library with private;
>       This_Library: in out Some_Library;
>    package Iterator is
>       function More return Boolean;
>       function Next return Book'Class;
>    end Iterator;
>
> private
>    ...
> end Libraries;
>
>
>    The body of Iterator will call (abstract) primitives on Libraries.
> Of course, when Iterator is instantiated, it will be on a non-abstract
> class, so there will be actual code to call.  But that is not your
> worry.

But I'm not sure this is what I want.  Unless there's something else
I'm missing, having an Iterator generic package whose body calls
abstract primitives on Libraries isn't what I want.

Let me try to go into more detail.  My original package spec looked
something like this:

    package Library_Package is
        type Library is abstract tagged null record;
        type Book is abstract tagged null record;
        type Scan_Info is abstract tagged null record;  -- (my iterator)
        procedure Scan_By_Title ... is abstract;
        function More_Books ... is abstract;
        procedure Next_Book ... is abstract;
        procedure Close_Scan ... is abstract;
    end Library_Package;

What I envisioned here is that different packages could deal with
different implementations of the library.  For example, I could
perhaps define something like

    package Amazon_Library_Package is
        type Library is new Library_Package.Library with private;
        type Book is new Library_Package.Book with private;
        etc.
    end Amazon_Library_Package;

where the purpose of this package is to define a "library" as all the
books in amazon.com.  The code for Scan_By_Title, More_Books,
Next_Book, as well as the private parts of the types I've defined,
would be set up specifically to FTP to amazon.com and send it commands
that cause amazon.com to return the information needed to implement
these functions.  (Note: I'm just pretending that amazon.com would
support this kind of thing.)  Similarly, another package,
B_Tree_Library_Package, might allow the program to use a file as a
library, where all the entries in the library are organized as a
B-tree, and so on.

So given that Scan_By_Title, More_Books, and Next_Book would have to
be coded specially for each implementation of Library_Package, I don't
see how setting up a generic iterator the way you've done it solves
the problem.

Also, when you say that the body of Iterator calls abstract primitives
on Libraries, I don't see how those primitives would be written.  It
seems like the abstract primitives I'd have to define in Libraries
would be, essentially, the same Scan_By_Title, More_Books, Next_Book,
etc. routines I already tried to define, and those would have the same
problem with OUT parameters that I already complained about.  So it
seems like all you've done is pushed the problem one level back.  I'll
grant that you could implement these primitives (perhaps in the
private part of Libraries) using a "dirty" method that uses accesses
to the abstract types as OUT parameters, and provide Iterator as a
"clean" interface to the outside world to avoid the dirty stuff.  Is
this what you were getting at with your response?  (Personally,
though, I don't see much benefit from adding this extra layer.)

>  > What is the cleanest way to accomplish what I'm trying to do?  This
>  > looks like such a typical use of polymorphism that I'd be surprised if
>  > there were no intuitive way to do it.
>
>    Now to write your Scan_by_Title, lets make it a child of Libraries:
>
>   generic
>     type Some_Library is new Library with private;
>   procedure Libraries.Scan_By_Title (Lib : in Some_Library;
>                                  Reg_Expression : in String;
>                                  Scan           : out Scan_Info;
>                                  RE_Error       : out Boolean);
>
>   procedure Libraries.Scan_By_Title (Lib : in Some_Library;
>                                  Reg_Expression : in String;
>                                  Scan           : out Scan_Info;
>                                  RE_Error       : out Boolean) is
>     ...
>     package Local_Iterator is new Libraries.Iterator(Some_Library, Lib);
>   begin
>     ...
>     while Local_Iterator.More loop
>       Process_Book(Local_Iterator.Next, {other parameters});
>     end loop;
>   end Libraries.Scan_By_Title;
>
>   I made this a child of Libraries for exposition purposes, you may
> want to have Scan_By_Title as an abstract primitive of the Library
> type and in effect, require that all non-abstract types derived from
> Library provide a body, or you could make it a non-abstract primitive.
> My leaning is to provide the Iterator as a child of Libraries, but to
> provide the search function as an abstract primitive.  In other words,
> some Library implementations may not have a concept of an ordering
> among books, but might still provide a search mechanism.

Unfortunately, you've reduced some flexibility by doing this, because
there's no guarantee that Process_Book (whatever it is---you haven't
defined it---is it a generic subprogram parameter?) is going to be
easy to write.  I often define iterators as four routines (initialize,
test-for-more, get-next, close) instead of, say, writing a generic
"do-this-for-all-the-books" routine (or a "do-for-all" routine that
takes an access-to-subprogram parameter), precisely to give myself
this flexibility.  For example, I might want to stop the iterator
after 10 books, because I only have room on the screen to display 10,
and I want to wait for the user to input a "go to next page" command
before bothering to retrieve the next 10.  This would be especially
necessary when FTP'ing from amazon.com; you don't want to have to
query for the entire set of matches until you know you'll need them.
Or, maybe I want to display three books on each line:

    begin
        Scan_By_Title (Lib, Title_Pattern, List_Scan, Error);
        if Error then ... end if;
        while More_Books (List_Scan) loop
            Next_Book (List_Scan, Book);
            Title1 := new String' (Title (Book));
            if not More_Books (List_Scan) then
                Title2 := null;
            else
                Next_Book (List_Scan, Book);
                Title2 := new String' (Title (Book));
            end if;
            if not More_Books (List_Scan) then
                Title3 := null;
            else
                Next_Book (List_Scan, Book);
                Title3 := new String' (Title (Book));
            end if;
            Text_IO.Put_Line (Make_One_Line_Out_Of_Three_Titles
                                 (Title1, Title2, Title3));
        end loop;
        Close_Scan (List_Scan);
    end List_Books_With_Matching_Titles;

My point here is that there may well be cases where a simple
"execute-the-same-code-for-every-item-iterated" approach isn't the
best, and I don't see a reason why I would want to be locked into that
approach, the way your Scan_By_Title routine seems to.  (The above
example would actually be pretty easy to fit into the Process_Book
approach, but that's not relevant.)

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

I'll look at my real-life code to see if it would benefit from coding
an iterator as you suggest.  For now, though, I've worked around my
problem by using access types for the OUT parameters.

                                -- Adam

-----== 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] 10+ messages in thread

* Re: How to Use Abstract Data Types
  1998-04-22  0:00 adam
  1998-04-23  0:00 ` Jacob Sparre Andersen
@ 1998-04-30  0:00 ` Robert I. Eachus
       [not found]   ` <matthew_heaney-ya023680003004981709380001@news.ni.net>
  1 sibling, 1 reply; 10+ messages in thread
From: Robert I. Eachus @ 1998-04-30  0:00 UTC (permalink / raw)



In article <6hm556$95u$1@nnrp1.dejanews.com> adam@irvine.com writes:

 >  But it looks like this isn't going to work.  If I were to write a
 >  procedure that lists all the books in a library whose titles match,
 >  I'd want to be able to write:

 >      procedure List_Books_With_Matching_Titles
 >		     (Lib           : in Library'Class;
 >		      Title_Pattern : in String) is
 >	   ... declarations
 >      begin
 >	   Scan_By_Title (Lib, Title_Pattern, List_Scan, Error);
 >	   if Error then
 >	       Insult_The_User;
 >	       return;
 >	   end if;
 >	   while More_Books (List_Scan) loop
 >	       Next_Book (List_Scan, The_Book_To_List);
 >	       List_Book (The_Book_To_List);
 >	   end loop;
 >	   Close_Scan (List_Scan);
 >      end List_Books_With_Matching_Titles;

 >  But I don't see how this can be done, since I can't declare List_Scan.
 >  I can't declare it as Library_Package.Scan_Info since that is an
 >  abstract type...
-- Actually you can have non-abstract operations of abstract types,
-- but there is a better solution here.

 > Am I missing something trivial here?

-- Yes, but you can be forgiven because it is not trivial in many OO
-- langauges.  There are cases where you have to use access parameters
-- and all that to duplicate the normal way of doing iterators in
-- other languages.  In Ada, you are always better off making
-- iterators objects, but in Ada 95 the much cleaner way of doing
-- iterators is to use instances of generic packages as the iterator
-- objects.  Sounds compilicated, but it isn't.  First, we will
-- realize that Books and libraries are separate abstractions:

package Books is

   type Book is ...;
   function Title(B: Book) return String;
   ...
end Books;

with Books
package Libraries is

   type Library is abstract tagged null record;

   -- various abstract operations on Libraries.

   generic
      type Some_Library is new Library with private;
      This_Library: in out Some_Library;
   package Iterator is
      function More return Boolean;
      function Next return Book'Class;
   end Iterator;
 
private
   ...
end Libraries;
  

   The body of Iterator will call (abstract) primitives on Libraries.
Of course, when Iterator is instantiated, it will be on a non-abstract
class, so there will be actual code to call.  But that is not your
worry.

 > What is the cleanest way to accomplish what I'm trying to do?  This
 > looks like such a typical use of polymorphism that I'd be surprised if
 > there were no intuitive way to do it.

   Now to write your Scan_by_Title, lets make it a child of Libraries:

  generic
    type Some_Library is new Library with private;
  procedure Libraries.Scan_By_Title (Lib : in Some_Library;
                                 Reg_Expression : in String;
                                 Scan           : out Scan_Info;
                                 RE_Error       : out Boolean);

  procedure Libraries.Scan_By_Title (Lib : in Some_Library;
                                 Reg_Expression : in String;
                                 Scan           : out Scan_Info;
                                 RE_Error       : out Boolean) is
    ...
    package Local_Iterator is new Libraries.Iterator(Some_Library, Lib);
  begin
    ...
    while Local_Iterator.More loop
      Process_Book(Local_Iterator.Next, {other parameters});
    end loop;
  end Libraries.Scan_By_Title;

  I made this a child of Libraries for exposition purposes, you may
want to have Scan_By_Title as an abstract primitive of the Library
type and in effect, require that all non-abstract types derived from
Library provide a body, or you could make it a non-abstract primitive.
My leaning is to provide the Iterator as a child of Libraries, but to
provide the search function as an abstract primitive.  In other words,
some Library implementations may not have a concept of an ordering
among books, but might still provide a search mechanism.
  








--

					Robert I. Eachus

with Standard_Disclaimer;
use  Standard_Disclaimer;
function Message (Text: in Clever_Ideas) return Better_Ideas is...




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

* Re: How to Use Abstract Data Types
@ 1998-05-04  0:00 adam
  1998-05-06  0:00 ` Robert I. Eachus
  0 siblings, 1 reply; 10+ messages in thread
From: adam @ 1998-05-04  0:00 UTC (permalink / raw)



Matthew Heaney wrote:

> What's wrong with the iterator-as-type technique?
>
> package Libraries is
>
>    type Root_Library is abstract tagged null record;
> ...
>    type Library_Iterator (Library : access Root_Library'Class) is limited
> private;
>
>    function Is_Done (Iterator : Library_Iterator) return Boolean;
>
>    function Get_Book (Iterator : Library_Iterator) return Book'Class;
>
>    procedure Advance (Iterator : in out Library_Iterator);
> ...
> end;
>
> declare
>    Library : aliased My_Library;
>    Iterator : Library_Iterator (Library'Access);
> begin
> ...
>    while not Is_Done (Iterator) loop
>       ... Get_Book (Iterator) ...
>       Advance (Iterator);
>    end loop;
> ...
> end;

I'm confused about how this should work.  As I noted in my response to
Robert Eachus, the purpose of setting things up as abstract types was
so that I could define new concrete types that represent different
implementation of the library.  I might have a package
Amazon_Library_Package that treats the set of books in amazon.com as a
library, and another package that uses a file of books set up as a
B-tree, etc.

Given this, it seems to me that the Library_Iterator type would also
be abstract, since each of the packages that defines concrete types
would keep different information in its iterator, depending on what
type of implementation it's using.  In any case, I don't see how this
type could be made "private", since the Libraries package, as declared
above, wouldn't have any idea what data is supposed to go into it.

When I tried making the Library_Iterator type abstract, I got nowhere,
since I wasn't able to define a type extension.  I tried this (note: I
used shorter names than yours):

    type Iterator (Lib : access Library'class) is
            abstract tagged limited null record;

and later, in another package:

    type Test_Library is new Library_Package.Library with private;
    type Test_Book is new Library_Package.Book with private;
    type Test_Iterator (Lib : access Test_Library) is new
        Library_Package.Iterator with private;

But I couldn't figure out how to declare Test_Iterator.  GNAT gave me
"unconstrained type not allowed in this context."

Anyway, I'm listing my entire test program below.  Hopefully, it
should be easy to see what I'm trying to accomplish; maybe you or
someone else can figure out how I can do it correctly.

                                -- thanks, Adam

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

package Library_Package is

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

    type Iterator (Lib : access Library'class) is
            abstract tagged limited null record;

    function The_Library return Library is abstract;

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

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

    function Is_Done (Iter : Iterator) return boolean is abstract;

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

    procedure Advance (Iter : in out Iterator) 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_Library_Acc is access all Test_Library;
    type Test_Iterator (Lib : access Test_Library) is new
        Library_Package.Iterator with private;           -- ????????????????

    function The_Library return Test_Library;
    function Title (Bk : Test_Book) return string;
    procedure Scan_For_Substring (Iter   : in out Test_Iterator;
                                  Substr : in string);
    function Is_Done (Iter : Test_Iterator) return boolean;
    function Get_Book (Iter : Test_Iterator) return Test_Book;
    procedure Advance (Iter : in out Test_Iterator);

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_Book is new Library_Package.Book with record
        Info : Book_Info;
    end record;

    type Test_Iterator (Lib : access Library'class) is new
            Library_Package.Iterator with record
        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) with 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) 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 (Iter   : in out Test_Iterator;
                                  Substr : in string) is
    begin
        Iter.Search_String := new string' (Substr);
        Iter.Index := My_Library'first;
        Search (Iter);
    end Scan_For_Substring;

    function Is_Done (Iter : Test_Iterator) return boolean is
    begin
        return (Iter.Index > My_Library'last);
    end Is_Done;

    function Get_Book (Iter : Test_Iterator) return Test_Book is
    begin
        return My_Library (Iter.Index);
    end Get_Book;

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

end Test_Library_Package;


with Library_Package;
package List_Package is
    procedure List_Books (Lib    : in out Library_Package.Library'class;
                          Substr : in string);
end List_Package;


with Text_IO;
package body List_Package is

    procedure List_Books (Lib    : in out Library_Package.Library'class;
                          Substr : in string) is
        Iter : Library_Package.Iterator (Lib'access);
    begin
        Library_Package.Scan_For_Substring (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 Libtest2 is
    The_Lib : Test_Library_Package.Test_Library;
begin
    The_Lib := Test_Library_Package.The_Library;
    List_Package.List_Books (The_Lib, "m");
end Libtest2;

-----== 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] 10+ messages in thread

* Re: How to Use Abstract Data Types
       [not found]   ` <matthew_heaney-ya023680003004981709380001@news.ni.net>
@ 1998-05-05  0:00     ` Stephen Leake
  1998-05-05  0:00       ` Matthew Heaney
  0 siblings, 1 reply; 10+ messages in thread
From: Stephen Leake @ 1998-05-05  0:00 UTC (permalink / raw)



Matthew Heaney wrote:

> <snip>
> What's wrong with the iterator-as-type technique?
>
> package Libraries is
>
>    type Root_Library is abstract tagged null record;
> ...
>    type Library_Iterator (Library : access Root_Library'Class) is limited
> private;
>
>    function Is_Done (Iterator : Library_Iterator) return Boolean;
>
>    function Get_Book (Iterator : Library_Iterator) return Book'Class;
>
>    procedure Advance (Iterator : in out Library_Iterator);
> ...
> end;
>
> declare
>    Library : aliased My_Library;
>    Iterator : Library_Iterator (Library'Access);
> begin
> ...
>    while not Is_Done (Iterator) loop
>       ... Get_Book (Iterator) ...
>       Advance (Iterator);
>    end loop;
> ...
> end;
>
> This is the technique I use throughout the ACL.  In particular, it's the
> technique I used for the B-tree packages a few cla readers have asked for.

 I like this technique, too, but one problem I have with it is it assumes
read-write access to the Library. Suppose I want to implement Find:

function Find (Title : in String; Library : in My_Library) return Book'class
is
    Iterator : Library_Iterator (Library'access); -- illegal
begin
    ...
end Find;

Since the Library parameter is "in", you cannot use it as the access
discriminant. The only way around this (that I have found) is to restructure
Find to be a procedure, with Library "in out" and the Book result as an "out"
parameter.

With the generic package iterator:
   generic
      type Some_Library is new Library with private;
      This_Library: in  Some_Library;
   package Iterator is
      function More return Boolean;
      function Next return Book'Class;
   end Iterator;

"This_Library" is now read-only.

Is there a good way to get read-only access with Iterator_Type?

-- Stephe





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

* Re: How to Use Abstract Data Types
  1998-05-05  0:00     ` Stephen Leake
@ 1998-05-05  0:00       ` Matthew Heaney
  1998-05-06  0:00         ` Stephen Leake
  0 siblings, 1 reply; 10+ messages in thread
From: Matthew Heaney @ 1998-05-05  0:00 UTC (permalink / raw)



In article <354F5C4D.DFF8286E@gsfc.nasa.gov>, Stephen Leake
<stephen.leake@gsfc.nasa.gov> wrote:

(start of quote)
I like this technique, too, but one problem I have with it is it assumes
read-write access to the Library. Suppose I want to implement Find:

function Find (Title : in String; Library : in My_Library) return Book'class
is
    Iterator : Library_Iterator (Library'access); -- illegal
begin
    ...
end Find;

Since the Library parameter is "in", you cannot use it as the access
discriminant.
(end of quote)

If you're using GNAT, then you can use the Unrestricted_Access attribute, ie

   Iter : Lib_Iter (Lib'Unrestricted_Access);
begin
...

This gives you the ability to make state changes behind the scenes (or,
here, supply an in param as an actual discriminant), even though the object
is publically read-only.  (In Meyer's terminology, you change the
"concrete" state without changing the "abstract" state.)

C++ programmers take this ability for granted, because you can "cast away
const."  It's a bummer you can't do that portably in Ada 95.  Oh, well. 
Maybe some programmer will write another article in JOOP explaining that we
need to "extend the syntax" of Ada 95...


(start of quote)
The only way around this (that I have found) is to restructure
Find to be a procedure, with Library "in out" and the Book result as an "out"
parameter.
(end of quote)

Not necessarily.  You can keep the functional form by making library an
access parameter:

fuction Find (Title : String; Lib : access My_Lib) return Book'Class is
  Iter : Lib_Iter (Lib);
begin
   ...

Now the code is completely portable too.

Yes, it seems like  a bummer that I should have to make a param in out or
access, even though it's read-only.  But this is just a "feature" of the
language.

(start of quote)
With the generic package iterator:
   generic
      type Some_Library is new Library with private;
      This_Library: in  Some_Library;
   package Iterator is
      function More return Boolean;
      function Next return Book'Class;
   end Iterator;

"This_Library" is now read-only.
(end of quote)

I haven't played around with generic packages as iterators - though I have
imported iterators as a generic formal parameter.  See my follow-up post
that answers Adam's questions.

(start of quote)
Is there a good way to get read-only access with Iterator_Type?
(end of quote)

Non-portable way (GNAT only): yes, using O'Unrestricted_Access.

Portable way: no.   You have to either pass the param as an access param
(works for any kind of type, even non-tagged types) or as in out (works for
tagged types only).




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

* Re: How to Use Abstract Data Types
  1998-04-30  0:00 How to Use Abstract Data Types adam
@ 1998-05-06  0:00 ` Robert I. Eachus
  0 siblings, 0 replies; 10+ messages in thread
From: Robert I. Eachus @ 1998-05-06  0:00 UTC (permalink / raw)



In article <6ib2o9$4gq$1@nnrp1.dejanews.com> adam@irvine.com writes:

 > Also, when you say that the body of Iterator calls abstract primitives
 > on Libraries, I don't see how those primitives would be written.  It
 > seems like the abstract primitives I'd have to define in Libraries
 > would be, essentially, the same Scan_By_Title, More_Books, Next_Book,
 > etc. routines I already tried to define, and those would have the same
 > problem with OUT parameters that I already complained about.

   No problem.  That went away when I moved the type Book out of the
Libraries package.  In some other OO languages that sort of confusion
between classes is necessary.  In Ada, such a confusion creates many
more problems than it solves.

   Note that if your model requires a special Amazon_Book type, that
is fine.  You derive it from Book, and the functions can return
Book'CLASS.  In fact if you look at my example, Next returns
Book'CLASS.  The function is not polymorphic on Book, but its return value can
be any type derived from Book.

 > So it seems like all you've done is pushed the problem one level
 > back.  I'll grant that you could implement these primitives
 > (perhaps in the private part of Libraries) using a "dirty" method
 > that uses accesses to the abstract types as OUT parameters, and
 > provide Iterator as a "clean" interface to the outside world to
 > avoid the dirty stuff.  Is this what you were getting at with your
 > response?  (Personally, though, I don't see much benefit from
 > adding this extra layer.)

   No dirty methods required.  The reason for providing the
 abstraction is so that you can override the methods that require it,
 and inherit others, concealing those details from the user of the
 abstraction.

  > Unfortunately, you've reduced some flexibility by doing this, because
  > there's no guarantee that Process_Book (whatever it is---you haven't
  > defined it---is it a generic subprogram parameter?) is going to be
  > easy to write.

    Of course there is no such guarantee.  Your Amazon.com example
shows why.  I was just showing that the easy cases could be handled by
default. 

 > I often define iterators as four routines (initialize,
 > test-for-more, get-next, close) instead of, say, writing a generic
 > "do-this-for-all-the-books" routine (or a "do-for-all" routine that
 > takes an access-to-subprogram parameter), precisely to give myself
 > this flexibility.  For example, I might want to stop the iterator
 > after 10 books, because I only have room on the screen to display 10,
 > and I want to wait for the user to input a "go to next page" command
 > before bothering to retrieve the next 10.  This would be especially
 > necessary when FTP'ing from amazon.com; you don't want to have to
 > query for the entire set of matches until you know you'll need them.
 > Or, maybe I want to display three books on each line...

   All possible complications, or you might have five different
iterators based on these differing requirements.  The point is that
you would write the five iterators once each, the however many library
abstractions once each, and the same for books.  You would never have
to code the m by n by p possible combinations.

   And that is the key concept to grasp here.  Ada provides several
different methods for creating classes of objects.  They can all be
designed to compose with each other.  But if you confound classes,
like the Amazon library and Amazon books above, then they don't
compose.  A Barnes_and_Noble library class couldn't use the Amazon
book class, and more important, adding CDs to the program would
require changes all over.  In Ada keep separate abstractions separate
wherever possible.
--

					Robert I. Eachus

with Standard_Disclaimer;
use  Standard_Disclaimer;
function Message (Text: in Clever_Ideas) return Better_Ideas is...




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

* Re: How to Use Abstract Data Types
  1998-05-04  0:00 adam
@ 1998-05-06  0:00 ` Robert I. Eachus
  0 siblings, 0 replies; 10+ messages in thread
From: Robert I. Eachus @ 1998-05-06  0:00 UTC (permalink / raw)



In article <6ilt69$j0g$1@nnrp1.dejanews.com> adam@irvine.com writes:

  > I'm confused about how this should work...

   Yes, you are.

  > Anyway, I'm listing my entire test program below.  Hopefully, it
  > should be easy to see what I'm trying to accomplish; maybe you or
  > someone else can figure out how I can do it correctly...

   The point where you make the key mistake is right at the beginning:
  
  > package Library_Package is

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

   I could show you how to make it work from this point, but that
would be counterproductive. If you put the type Book in a different
package, then the rest is easy.  (And if, when you are finished you
want to recombine the two packages, the language won't stop you.  It
is just that once you confuse types like this you get confused.)  The
language problem is that with this construction you can't have a
function for Library that returns a Book:

  RM 3.9.2(12): "A given subprogram shall not be a dispatching
                 operation of two or more distinct tagged types."

   If you use the correct package layout above, then:

   function Find(L: in Library; Key: in String) return Book;

   should get you the right error message.  Since Book is abstract,
you can't return one.

   Now it appears that you need to create a doubly dispatching
operation.  One common case is where two different parameters of the
same type may have different tags.  (You create a dispatching
operation with one dispatching parameter and one class wide parameter,
which calls another operation which dispatches on the other
parameter.)  Much more usual is the case that is needed here.  You
need to declare operations of Library with class-wide Book parameters:

   function Find(L: in Library; Key: in String) return Book'CLASS;

   or whatever.  Notice that Find if it is defined in the same package
as Library will be a dispatching operation of Library.  Find may call
operations of Book which will dispatch to the operation for that
particular type of Book, but that is transparent when writing Find.

    Find is not a dispatching operation of Book, but since the
operations it calls on Book can dispatch, it behaves like one.  As I
said elsewhere, this ability to disentangle unrelated classes is
not unique to Ada.  However, in Ada it is if not required at least
strongly encouraged by the structure of the language.
--

					Robert I. Eachus

with Standard_Disclaimer;
use  Standard_Disclaimer;
function Message (Text: in Clever_Ideas) return Better_Ideas is...




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

* Re: How to Use Abstract Data Types
  1998-05-05  0:00       ` Matthew Heaney
@ 1998-05-06  0:00         ` Stephen Leake
  0 siblings, 0 replies; 10+ messages in thread
From: Stephen Leake @ 1998-05-06  0:00 UTC (permalink / raw)



Matthew Heaney wrote:

> In article <354F5C4D.DFF8286E@gsfc.nasa.gov>, Stephen Leake
> <stephen.leake@gsfc.nasa.gov> wrote:
>
> (start of quote)
> I like this technique, too, but one problem I have with it is it assumes
> read-write access to the Library. Suppose I want to implement Find:
>
> function Find (Title : in String; Library : in My_Library) return Book'class
> is
>     Iterator : Library_Iterator (Library'access); -- illegal
> begin
>     ...
> end Find;
>
> Since the Library parameter is "in", you cannot use it as the access
> discriminant.
> (end of quote)
>
> If you're using GNAT, then you can use the Unrestricted_Access attribute, ie
>
>    Iter : Lib_Iter (Lib'Unrestricted_Access);
> begin
> ...
>
> This gives you the ability to make state changes behind the scenes (or,
> here, supply an in param as an actual discriminant), even though the object
> is publically read-only.  (In Meyer's terminology, you change the
> "concrete" state without changing the "abstract" state.)
>
> C++ programmers take this ability for granted, because you can "cast away
> const."  It's a bummer you can't do that portably in Ada 95.  Oh, well.
> Maybe some programmer will write another article in JOOP explaining that we
> need to "extend the syntax" of Ada 95...
>

I've wondered if allowing "constant" in an access discriminant declaration would
do the trick:

type Read_Only_Library_Iterator (Library : access constant My_Library) is record
...

This seems like a reasonable syntax extension.

-- Stephe






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

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

Thread overview: 10+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
1998-04-30  0:00 How to Use Abstract Data Types adam
1998-05-06  0:00 ` Robert I. Eachus
  -- strict thread matches above, loose matches on Subject: below --
1998-05-04  0:00 adam
1998-05-06  0:00 ` Robert I. Eachus
1998-04-22  0:00 adam
1998-04-23  0:00 ` Jacob Sparre Andersen
1998-04-30  0:00 ` Robert I. Eachus
     [not found]   ` <matthew_heaney-ya023680003004981709380001@news.ni.net>
1998-05-05  0:00     ` Stephen Leake
1998-05-05  0:00       ` Matthew Heaney
1998-05-06  0:00         ` Stephen Leake

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