[comp.lang.modula2] Implementing Abstract Lists

dgil@pa.reuter.COM (Dave Gillett) (08/02/90)

Have you read _Abstract Data Types in Modula-2_, by R. Harrison of the 
Department of Electronics and Computer Science, University of Southampton, UK?
  
I picked up this book because it discusses implementation of list, queue, 
graph, and various sorts of tree structures in Modula-2.  I'd been hoping, 
particularly with the title's reference to abstract types, to find a general 
"list" implementation that might apply to lists of any sort, and so on.
  
So I was severely disappointed to discover that the "List" module presented 
does not in fact deal with lists in the abstract, but with lists of things of 
type "ItemType" which is imported from some other module.  So in a typical 
real-world program, if I have three types of things that I want lists of, I 
need three (almost but not quite identical) copies of the List module as 
presented.
  
This is absolutely not acceptible, and I fear that it may illustrate the 
difference between academic theory and engineering practice.
  
I've pretty much resolved that my own "List" module is going to need, as a 
parameter, the offset from the start of a record (of whatever type are in this 
list) to a field which contains the link field(s) and any other information 
that the List module needs.  (One of the side effects is that I can have a 
single set of records participate in multiple lists, in different orders.)
  
So I'm looking for a simple, and preferably portable, way to (a) calculate, 
and (b) use, the offset.  Pointer arithmetic is possible, but I'm developing 
on the PC so that approach may not be simple or portable.  Any suggestions?

lins@Apple.COM (Chuck Lins) (08/02/90)

In article <290@saxony.pa.reuter.COM> dgil@pa.reuter.COM (Dave Gillett) writes:
[comments on one books inadequacy for generic lists]

Without trying to be self-serving, you may want to look at my own series,
"The Modula-2 Software Component Library", specifically Volume 2, which
covers generic lists (as well as queues and deques). From your discussion it
sounds as if these will be more appropriate for your needs. I should note that
Volumes 2-4 require imports from modules in Volume 1. The publisher is
Springer-Verlag.


-- 
Chuck Lins               | "Is this the kind of work you'd like to do?"
Apple Computer, Inc.     | -- Front 242
20525 Mariani Avenue     | Internet:  lins@apple.com
Mail Stop 37-BD          | AppleLink: LINS@applelink.apple.com
Cupertino, CA 95014      | "Self-proclaimed Object Oberon Evangelist"
The intersection of Apple's ideas and my ideas yields the empty set.

manis@cs.ubc.ca (Vincent Manis) (08/02/90)

Sorry, Modula-2 isn't really suitable for generic "container" ADT's such
as List, Stack, Queue, etc. (i.e., all the stuff of computer science).
There is a way to do it, namely by using ADDRESS values, and casting the
actual parameters to type ADDRESS in calls to the ADT procedures, but
it's a crock. 

Wirth has abandoned Modula. His new language, Oberon, provides garbage
collection, and allows a limited form of structure inheritance. The
result is that you can have a List module. You can then declare an
IntegerList record type, inheriting from List. (Note that Oberon isn't
object-oriented: inheritance affects fields, not methods.) The List
procedures will work with IntegerLists with no problem.

I switched from Modula-2 to C in my data structures course last year.
Afterwards, I really felt that I had lost almost nothing. This isn't a
compliment to C, but a criticism of Modula. It really doesn't help you
very much with the tough problems. 
--
\    Vincent Manis <manis@cs.ubc.ca>      "There is no law that vulgarity and
 \   Department of Computer Science      literary excellence cannot coexist."
 /\  University of British Columbia                        -- A. Trevor Hodge
/  \ Vancouver, BC, Canada V6T 1W5 (604) 228-2394

mbenveni@irisa.fr (Marc Benveniste) (08/02/90)

From article <290@saxony.pa.reuter.COM>, by dgil@pa.reuter.COM (Dave Gillett):
>   
> So I'm looking for a simple, and preferably portable, way to (a) calculate, 
> and (b) use, the offset.  Pointer arithmetic is possible, but I'm developing 
> on the PC so that approach may not be simple or portable.  Any suggestions?

I have used the following interface to optain genericity and still rely
on Modula-2 strong typing. Portability is isolated in the SYSTEM and
Storage modules. I'm sorry for posting sources, but I hope these sources
can be useful to many.

*******************************************************************************
*******************************************************************************

DEFINITION MODULE Lists;
(*==========================================================================

  Global Description :  This module provides generic linked lists

      A list is a couple ( L, IO ) where L is the list structure and IO is
  a variable of the type of the elements that L can handle. When creating
  the structure a variable must be assigned to it. The role of that variable
  is double:
             1)- It provides the base type of the list structure,
             2)- it is the port to the list, insuring type checking.

     Operations on the list structure IMPLICITELY use the IO variable.
  That's why these operations are described as side effects. A single IO
  variable may be the port to many lists as long as all lists are of the
  same base type.
                               _______________
                               __: WARNING :__

     The port of a list structure MUST have the same LIFELENGTH and SCOPE
  as the structure itself.

  ________________________________________________________________________

                                  FirstEdit: 23/03/87
                                  LastEdit :  2/07/87
  ________________________________________________________________________

               Author : Marc Benveniste
               System : Logitech MODULA-2/86 V. 2.05
     Developped while
        working at    : IIMAS-UNAM,
                        Apdo. Postal 20-726,
                        Mexico D.F., 01000
                        MEXICO
 ===========================================================================*)

    FROM SYSTEM IMPORT
    (* Type *)         ADDRESS;

    EXPORT QUALIFIED
    (* Type *)         List,
    (* Var *)          ListError,
    (* Procedure *)    NewList, IsEmpty, First, Remove,
                       Insert, Next, Dispose;

    TYPE
      List;

    VAR
      ListError : CARDINAL;

 (*______: Possible error codes :__________________________________________

          0 -------->  No error ocurred,
          1 -------->  General failure,
          2 -------->  Out of memory,
          3 -------->  Tried to REMOVE or FIRST on an empty list or position,
          4 -------->  Tried to DISPOSE of a non-empty list,
          5 -------->  No next element available.
  _________________________________________________________________________*)


  PROCEDURE NewList(IOPort: ADDRESS; ElemTypeSize: CARDINAL): List;
 (*______________________________________________________________________

       NewList creates, if possible, a list ready to handle a given TYPE
   of objects. The only way to interact with the list is through it's
   port. The port must be a VAR  with the same life length and scope as
   the new list.

   In --> IO ::=  The address of the port variable of list.
          TypeSize ::=  Size of the TYPE of the list's port.
   Out -> An empty list ready to handle elements of size TypeSize
          through port at address IO if no error ocurred.

   SideEffect ---> ListError is set to 0 or 2.
   ______________________________________________________________________*)


  PROCEDURE IsEmpty(VAR L : List): BOOLEAN;
(*_________________________________________________________________________

     IsEmpty is True if L is an empty list; False otherwise.

  In  ----> L ::= A list obtained by means of a successful NewList call.
  Out ----> L ::= Untouched
            IsEmpty ::= TRUE if L is empty; FALSE otherwise.

  SideEffect ---> ListError is set to 0 or 1.
  _________________________________________________________________________*)


  PROCEDURE First(VAR L: List);
(*_________________________________________________________________________

      First places in the port assigned to L the head element of the list
  structure L, and makes it the current element. ListError may be 0,1 or 3.

  In  ----> L ::= A list obtained by means of a successful New call.
  Out ----> L ::= The Head  of L has become the current element

  SideEffect ---> A copy of the Head of L is in its port.
                  ListError is set to 0,1 or 3.
  _________________________________________________________________________*)

  PROCEDURE Insert(VAR L: List);
(*_________________________________________________________________________

      Insert makes a copy of the element in the port assigned to L and
  inserts it in the list structure immediately before the current element;
  The inserted element becomes the current one. If L is empty then the copy
  becomes the head and current element. ListError may be 0,1 or 2.

  In         ---> L = Any legal List.
  Out        ---> L = The input list with a copy of it's port's content
                      inserted in front of it's current element.
  SideEffect ---> ListError is set according to the result of the operation.
                  The current element of the list is the inserted one if
                  ListError is 0.
  _________________________________________________________________________*)


  PROCEDURE Remove(VAR L: List);
(*_________________________________________________________________________

     The current element is removed from the list. Next element becomes the
  current one. A copy of that element is in the port associated to L.
  ListError may be 0,1,3 or 5.

  In         ---> L = Any legal List.
  Out        ---> L = The input list with it's current element removed.
  SideEffect ---> ListError is set to 0,1,3 or 5.
                  The List's port contains a copy of the current element,
                  if any.
  _________________________________________________________________________*)


  PROCEDURE Next(VAR L: List);
(*_________________________________________________________________________

      A copy of the next element of the current one is available in the
  port associated to L. That element also becomes the current one.
  ListError may be 0,1 or 5.

  In         ---> L = Any legal List.
  Out        ---> L = The input list.
  SideEffect ---> ListError is set to 0,1 or 5.
                  A copy of the next element, if any, of the current one
                  is in the port. That one also becomes the current one.
  _________________________________________________________________________*)


  PROCEDURE Dispose(VAR L: List);
(*_________________________________________________________________________

      If L is empty, Dispose frees the allocated memory and L becomes an
  invalid data. ListError may be 0,1 or 4.

  In         ---> L = Any legal empty List.
  Out        ---> L = Meaningless data if ListError = 0; same data otherwise.
  SideEffect ---> ListError is set to 0,1 or 4.
_________________________________________________________________________*)


END Lists.

IMPLEMENTATION MODULE Lists;
(*==========================================================================

  Global Description :  This module implements generic linked lists
  ________________________________________________________________________

                                  FirstEdit: 18/05/87
                                  LastEdit : 15/01/88
  ________________________________________________________________________

               Author : Marc Benveniste
               System : Logitech MODULA-2/86 V. 2.05
     Developped while
        working at    : IIMAS-UNAM,
                        Apdo. Postal 20-726,
                        Mexico D.F., 01000
                        MEXICO
 ===========================================================================*)


  FROM SYSTEM IMPORT
    (* Type *)         ADDRESS, WORD,
    (* Procedure *)    TSIZE;

  FROM Storage IMPORT
    (* Procedure *)    ALLOCATE, DEALLOCATE, Available;

  FROM CopyMem IMPORT
    (* Procedure *)    CopyByte, CopyWord;  (* Address arithmetics *)


  TYPE
    List       = POINTER TO Descriptor;
    Link       = POINTER TO Node;
    Descriptor = RECORD
                   IOBuffer    : ADDRESS;   (* Port to List *)
                   TSize       : CARDINAL;  (* Size of Elements *)
                   WordUnits   : BOOLEAN;   (* T if Word; F if Bytes *)
                   Head,PreCur,             (* Head, Precurrent & Current *)
                   Current     : Link       (* elements of List *)
                 END;
    Node       = RECORD
                   Elem : ADDRESS;          (* Ptr to Copy of Elem *)
                   Next : Link
                 END;


  PROCEDURE NewList(IOPort: ADDRESS; ElemTypeSize: CARDINAL): List;
    VAR
      L : List;
      A : BITSET;
  BEGIN
    IF Available(TSIZE(Descriptor))
      THEN
        ListError := 0;
        A := BITSET(ElemTypeSize);
        NEW(L);
        WITH L^ DO
          IOBuffer := IOPort;
          IF (0 IN A)
           THEN TSize := ElemTypeSize; WordUnits := FALSE
           ELSE TSize := ElemTypeSize DIV 2; WordUnits := TRUE
          END;
          Head     := NIL;
          PreCur   := NIL;
          Current  := NIL
        END; (* with *)
        RETURN L
    END; (* if *)
    ListError := 2;
    RETURN NIL
  END NewList;


  PROCEDURE IsEmpty(VAR L : List): BOOLEAN;
  BEGIN
    IF L = NIL
      THEN
        ListError := 1;
        RETURN FALSE
      ELSE
        ListError := 0;
        RETURN (L^.Head = NIL)
    END (* if *)
  END IsEmpty;

  PROCEDURE First(VAR L: List);
  BEGIN
    ListError := 0;
    IF    L = NIL
      THEN ListError := 1
    ELSIF L^.Head = NIL
      THEN ListError := 3
    ELSIF L^.WordUnits
      THEN CopyWord(L^.Head^.Elem,L^.IOBuffer,L^.TSize)
      ELSE CopyByte(L^.Head^.Elem,L^.IOBuffer,L^.TSize)
    END; (*if*)
    IF ListError = 0
     THEN
      WITH L^ DO
        Current := Head;
        PreCur  := Head
      END (* with *)
    END (* if *)
  END First;

  PROCEDURE Insert(VAR L: List);
    VAR
      p : Link;
  BEGIN
    ListError := 0;
    IF    L = NIL
      THEN ListError := 1;
    ELSIF L^.WordUnits & Available(TSIZE(Node) + L^.TSize*2)
      THEN
        NEW(p);
        ALLOCATE(p^.Elem,L^.TSize*2);
        CopyWord(L^.IOBuffer,p^.Elem,L^.TSize)
    ELSIF NOT(L^.WordUnits) & Available(TSIZE(Node) + L^.TSize)
      THEN
        NEW(p);
        ALLOCATE(p^.Elem,L^.TSize);
        CopyByte(L^.IOBuffer,p^.Elem,L^.TSize)
      ELSE
        ListError := 2
    END; (*if*)
    IF ListError = 0
      THEN
        IF L^.Head = L^.Current
          THEN
            WITH L^ DO
              Current := p;
              Current^.Next := Head;
              Head := Current;
              PreCur := Head
            END (* with *)
          ELSE
            p^.Next := L^.Current;
            L^.Current := p;
            L^.PreCur^.Next := L^.Current
        END (* if *)
    END (* if *)
  END Insert;

  PROCEDURE Remove(VAR L: List);
    VAR
      p : Link;
  BEGIN
    IF    L = NIL
      THEN ListError := 1
    ELSIF L^.Current = NIL
      THEN ListError := 3
      ELSE
        p := L^.Current;
        WITH L^ DO
          IF Head = Current
            THEN
              Head := Current^.Next;
              Current := Head;
              PreCur := Head
            ELSE
              Current := Current^.Next;
              PreCur^.Next := Current
          END (* if *)
        END; (* with *)
        IF L^.Current = NIL
          THEN
            ListError := 5
          ELSE
            ListError := 0;
            WITH L^ DO
             IF WordUnits
              THEN CopyWord(Current^.Elem,IOBuffer,TSize)
              ELSE CopyByte(Current^.Elem,IOBuffer,TSize)
             END
            END
        END; (* if *)
        IF L^.WordUnits
         THEN DEALLOCATE(p^.Elem,L^.TSize*2)
         ELSE DEALLOCATE(p^.Elem,L^.TSize)
        END;
        DISPOSE(p)
    END (* if *)
  END Remove;

  PROCEDURE Next(VAR L: List);
  BEGIN
    IF    L = NIL
      THEN ListError := 1
    ELSIF (L^.Current = NIL) OR (L^.Current^.Next = NIL)
      THEN ListError := 5
      ELSE
        ListError := 0;
        WITH L^ DO
          PreCur  := Current;
          Current := Current^.Next;
          IF WordUnits
           THEN CopyWord(Current^.Elem,IOBuffer,TSize)
           ELSE CopyByte(Current^.Elem,IOBuffer,TSize)
          END
        END (* with *)
    END (* if *)
  END Next;

  PROCEDURE Dispose(VAR L: List);
  BEGIN
    IF    L = NIL
      THEN ListError := 1
    ELSIF L^.Head # NIL
      THEN ListError := 4
      ELSE
        ListError := 0;
        DISPOSE(L);
        L := NIL
    END (* if *)
  END Dispose;

BEGIN
  ListError := 0
END Lists.

jubo@rwthinf.UUCP (Juergen Boerstler) (08/02/90)

mbenveni@irisa.fr (Marc Benveniste) writes:

>From article <290@saxony.pa.reuter.COM>, by dgil@pa.reuter.COM (Dave Gillett):
>>   
>> So I'm looking for a simple, and preferably portable, way to (a) calculate, 
>> and (b) use, the offset.  Pointer arithmetic is possible, but I'm developing 
>> on the PC so that approach may not be simple or portable.  Any suggestions?

>I have used the following interface to optain genericity and still rely
>on Modula-2 strong typing. Portability is isolated in the SYSTEM and
>Storage modules. I'm sorry for posting sources, but I hope these sources
>can be useful to many.

>... implementation deleted

I cannot see where this approach relies on the (relatively) strong typing
of Modula-2, nor is it very portable (if at all). The following list of
problems can be stated:

(1) List elements have to be passed per 'ADDRESS' (-> limited type checking,
    because all pointers (and CARDINAL usually) are compatible with it).
(2) The implementation has an elegant solution to the problem of copying
    bytestrings, namely not showing their implementation (-> limited
    portability, because "standard" Modula-2 only can deal with words of
    memory, which have an implementation dependent size. Therefore copying
    values of "length MOD bytesPerWord <> 0" is very tricky in most Systems).
(3) The interface is not comprehensive enough (-> limited usability, because
    a lot of ressources are not present, e.g. 'InsertBeforeGivenElement',
    'IsGivenElementInList', 'LengthOfList', ....).
(4) There are no procedure parameters to the ressources (esp. 'NewList'
    -> see (3), because procedure parameters are needed for some of the
    more advanced features, e.g. 'SortList', 'DeleteDuplicates', ...).
(5) More suggestions?

In my opinion the approach attemted by C. Lins in
  'The Modula-2 Software Component Library' (by Springer)
is a good way to obtain generic adts in Modula-2 without enlarging the
language. But there are also some very interesting discussions about
adding generic (and object oriented) constructs/ features to the language,
which can be checked and filtered by preprocessors.

It would be very nice to have a discussion about such extensions including
preprocessors to "standard" Modula-2.

jubo

**************************************************************************
*  Juergen Boerstler              *  e-mail: jubo@rwthi3.uucp            *
*  Lehrstuhl fuer Informatik III  *                                      *
*  Ahornstrasse 55                *  phone:  +49/ 241/ 80-7216           *
*  D-5100 Aachen                  *                                      *
*  West Germany                   *                                      *
**************************************************************************

mbenveni@irisa.fr (Marc Benveniste) (08/03/90)

From article <3275@rwthinf.UUCP>, by jubo@rwthinf.UUCP (Juergen Boerstler):
> I cannot see where this approach relies on the (relatively) strong typing
> of Modula-2, nor is it very portable (if at all). The following list of
> problems can be stated:
> 
> (1) List elements have to be passed per 'ADDRESS' (-> limited type checking,
>     because all pointers (and CARDINAL usually) are compatible with it).

 You should notice that the vulnerable operation on a list is the creation
one where the user may cheat passing a dummy address and a dummier size.
 If the user relies on the following protocol to initialise its lists,
type checking is assured from there on. Remember we don't have genericity
so it cannot be safe all the way. Please note that after creation, elements
are NOT passed per ADDRESS. They are assigned to a (typed) variable.
...
 FROM SYSTEM IMPORT TSIZE, ADR;
...
 VAR IO_Port, Item : AnyType;
     MyList : List
...
 MyList := NewList(ADR(IO_Port), TSIZE(AnyType));
...
 IO_Port := Item;
 Insert(MyList);
...
 
> (3) The interface is not comprehensive enough (-> limited usability, because
>     a lot of ressources are not present, e.g. 'InsertBeforeGivenElement',
>     'IsGivenElementInList', 'LengthOfList', ....).

 This is a highly subjective matter... I admit I only provide some basic
primitives. We would have to agree on what lists are. Any way, I just
wanted to show an example of an almost generic-type-safe list module.
If you have better ideas, please share them! :-)

> **************************************************************************
> *  Juergen Boerstler              *  e-mail: jubo@rwthi3.uucp            *
> *  Lehrstuhl fuer Informatik III  *                                      *
> *  Ahornstrasse 55                *  phone:  +49/ 241/ 80-7216           *
> *  D-5100 Aachen                  *                                      *
> *  West Germany                   *                                      *
> **************************************************************************

Marc Benveniste
IRISA
Campus de Beaulieu
35042 Rennes Cedex
FRANCE

cszthomas@qut.edu.au (08/03/90)

In article <8974@ubc-cs.UUCP>, manis@cs.ubc.ca (Vincent Manis) writes:
> Sorry, Modula-2 isn't really suitable for generic "container" ADT's such
> as List, Stack, Queue, etc. (i.e., all the stuff of computer science).
> There is a way to do it, namely by using ADDRESS values, and casting the
> actual parameters to type ADDRESS in calls to the ADT procedures, but
> it's a crock. 

Agreed.  In the early days of Modula-2 two of us tried setting up generics
in M2 and gave up because of poor language support.

> Wirth has abandoned Modula. His new language, Oberon, provides garbage
> collection, and allows a limited form of structure inheritance. The
> result is that you can have a List module. You can then declare an
> IntegerList record type, inheriting from List. (Note that Oberon isn't
> object-oriented: inheritance affects fields, not methods.) The List
> procedures will work with IntegerLists with no problem.

As a note, ETH has also developed an Object Oberon as well.

> I switched from Modula-2 to C in my data structures course last year.
> Afterwards, I really felt that I had lost almost nothing. This isn't a
> compliment to C, but a criticism of Modula. It really doesn't help you
> very much with the tough problems. 

I am curious has to how you justify this paragraph?  Granted M2 doesn't
support generics, but neither does C.  Then there are all of the facilities
in M2 that C doesn't have.

> --
> \    Vincent Manis <manis@cs.ubc.ca>      "There is no law that vulgarity and
>  \   Department of Computer Science      literary excellence cannot coexist."
>  /\  University of British Columbia                        -- A. Trevor Hodge
> /  \ Vancouver, BC, Canada V6T 1W5 (604) 228-2394

If I was in a nasty mood I would say: "Ah, UBC, that explains your ideas,
and that also explains why I never went to UBC."

Au revoir,

@~~Richard Thomas  aka. The AppleByter  --  The Misplaced Canadian~~~~~~~~~~~@
{ InterNet: R_Thomas@qut.edu.au           ACSNet:  richard@earth.qitcs.oz.au }
{ PSI:      PSI%505272223015::R_Thomas                                       }
@~~~~~School of Computing Science - Queensland University of Technology~~~~~~@

Pat.Terry@p101.f4.n494.z5.fidonet.org (Pat Terry) (08/05/90)

dgil@pa.reuter.COM (Dave Gillett) in <290@saxony.pa.reuter.COM> writes

 > So I was severely disappointed to discover that the "List" module 
 > does not in fact deal with lists in the abstract, but with lists of things 
 > of type "ItemType" which is imported from some other module.  So in a 
 > typical real-world program, if I have three types of things that I want 
 > lists of, I need three (almost but not quite identical) copies of the 
 > List module as presented.

I haven't got my copy of Harrison handy.  It's not true; you can use one copy 
if you are careful.  It's slightly messy, I concede.

    DEF MOD  OneHandler;
      TYPE One;
      (* all operations on One in fairly stereotyped form *)
    END OneHandler.

    DEF MOD TwoHandler;
      TYPE Two;
      (* all operations on Two ditto *)
    END TwoHandler.

Now these are opaque types.  So they are really addresses anyway.  So
make your ListHandler use things like

    TYPE LISTS = POINTER TO NODES
         NODES = RECORD
                   Data : SYSTEM.ADDRESS;
                   Link : LISTS
                 END

    PROCEDURE Push (VAR List : LISTS; Item : SYSTEM.ADDRESS)
      VAR Latest : LISTS;
      BEGIN
        New(Latest);
        Latest^.Link := List; Latest^.Data := Item;
        List := Latest
      END Push;

.....

Then with

     VAR x : OneHandler.One;
         y : TwoHandler.Two
         OneStack, TwoStack : LISTS

BEGIN
     Push (OneStack, SYSTEM.ADDRESS(x)) (* type cast *);
     Push (TwoStack, SYSTEM.ADDRESS(y));

Depending on how your system interprets compatibility for opaques you
might even get away with the simpler code below:

(FST on the PC allows it, Logitech, JPI, FTL, Collier and Quickmod do not; all 
accept the code above.

     Push (OneStack, x);
     Push (TwoStack, y);
     
Of course, you don't gain type checking benefits any longer - and it is
even messier if you want to stack other than opaque types.

If you want to play with generics in M-2 the author to look for is John Gough,
both in his text book, and in articles in JPAM.
 




--  
uucp: uunet!m2xenix!puddle!5!494!4.101!Pat.Terry
Internet: Pat.Terry@p101.f4.n494.z5.fidonet.org

Chip.Richards@p3.f18.n114.z1.fidonet.org (Chip Richards) (08/06/90)

In a message dated 1 Aug 90, dgil@pa.reuter.COM (Dave Gillett) wrote:

 > So I was severely disappointed to discover that the "List" module presented 
 > does not in fact deal with lists in the abstract, but with lists of things 
 > of type "ItemType" which is imported from some other module.  So in a 
 > typical real-world program, if I have three types of things that I want 
 > lists of, I need three (almost but not quite identical) copies of the List 
 > module as presented. 

Umm, gee, Dave, maybe I'm missing the point, here, but isn't this where a variant record would come in real handy?  As in

TYPE
   ThingType = ( aThing, anotherThing, lastThing ) ;
   ItemType = RECORD
      CASE ThingType OF
         aThing:
            fields for a thing
            |
         anotherThing:
            fields for another thing
            |
         lastThing:
            fields for last thing
      END  (* case *)
   END ;

Maybe I just misunderstood your problem, but using the above definition, one copy of the "List" module would handle three widely different types of things.

Chip


--  
uucp: uunet!m2xenix!puddle!114!18.3!Chip.Richards
Internet: Chip.Richards@p3.f18.n114.z1.fidonet.org

Peter.M..Perchansky@f101.n273.z1.fidonet.org (Peter M. Perchansky) (08/06/90)

Hello Chuck:

    Could you please send me more information about your Software Library series (netmail this node or send to the following address:

            Peter M. Perchansky
            211 South 5th Street
            Womelsdorf, PA  19567)



--  
uucp: uunet!m2xenix!puddle!273!101!Peter.M..Perchansky
Internet: Peter.M..Perchansky@f101.n273.z1.fidonet.org

Peter.M..Perchansky@f101.n273.z1.fidonet.org (Peter M. Perchansky) (08/06/90)

Hello:

    Wirth has not abandoned Modula-2.

    ...concerning ADT's... you can implement ADT's in Modula-2 using ARRAY OF WORD, ARRAY OF BYTE, or ADDRESS.

    You can also make use of PROCEDURE variables and Opaque types.



--  
uucp: uunet!m2xenix!puddle!273!101!Peter.M..Perchansky
Internet: Peter.M..Perchansky@f101.n273.z1.fidonet.org

Ron.Mckenzie@p1.f45.n104.z1.fidonet.org (Ron Mckenzie) (08/08/90)

 CL> From: lins@Apple.COM (Chuck Lins)
 CL> Date: 2 Aug 90 00:05:51 GMT
 CL> Organization: Apple Computer Inc, Cupertino, CA
 CL> Message-ID: <43543@apple.Apple.COM>
 CL> Newsgroups: comp.lang.modula2,comp.edu

 CL> In article <290@saxony.pa.reuter.COM> 
 CL> dgil@pa.reuter.COM (Dave Gillett) writes:
 CL> [comments on one books inadequacy for generic lists]

 CL> Without trying to be self-serving, you may want to 
 CL> look at my own series, "The Modula-2 Software 
 CL> Component Library", specifically Volume 2, ...
  
Chuck, is either Volume 3 or 4 available, yet?  And, the source code disk(s)?


--  
uucp: uunet!m2xenix!puddle!104!45.1!Ron.Mckenzie
Internet: Ron.Mckenzie@p1.f45.n104.z1.fidonet.org

Peter.M..Perchansky@f101.n273.z1.fidonet.org (Peter M. Perchansky) (08/08/90)

Hello:

    In a few days I will post my generic dequeue module to show how Modula-2 can handle generic lists.



--  
uucp: uunet!m2xenix!puddle!273!101!Peter.M..Perchansky
Internet: Peter.M..Perchansky@f101.n273.z1.fidonet.org

csgr@quagga.uucp (Geoff Rehmet) (08/09/90)

In article <13227.26b9800a@qut.edu.au> cszthomas@qut.edu.au writes:
>In article <8974@ubc-cs.UUCP>, manis@cs.ubc.ca (Vincent Manis) writes: 
>> I switched from Modula-2 to C in my data structures course last year.
>> Afterwards, I really felt that I had lost almost nothing. This isn't a
>> compliment to C, but a criticism of Modula. It really doesn't help you
>> very much with the tough problems.
>  
>I am curious has to how you justify this paragraph?  Granted M2 doesn't
>support generics, but neither does C.  Then there are all of the facilities
>in M2 that C doesn't have.

As a student myself, I would prefer to have my initial data structures
course in Modula-2 rather than C.  C, by allowing you to do clever things
also allows you too much room to shoot yourself in the foot, which 
beginners will very readily do.  (I did have my first data strucures course
in M2.)

It is far more reassuring for beginning students to have their errors 
pointed out to them by their compiler, rather than when their program
crashes (although many of my M2 programs have crashed first try).


(I'm not trying to have a go at C, I like both M2 and C.  So, netters, please 
don't start flaming about the relative merits and demerits of M2 and C!)


Cheers, Geoff.

-- 
Geoff Rehmet       |      Internet: csgr.quagga@f4.n494.z5.fidonet.org          
Rhodes University  |      Uninet  : csgr@quagga      
Grahamstown        |      UUCP    : ..uunet!m2xenix!quagga!csgr
-------------------+

Pat.Terry@p101.f4.n494.z5.fidonet.org (Pat Terry) (08/10/90)

 > Umm, gee, Dave, maybe I'm missing the point, here, but isn't this where a 
 > variant record would come in real handy?  As in
 > 
 > TYPE
 >    ThingType = ( aThing, anotherThing, lastThing ) ;
 >    ItemType = RECORD
 >       CASE ThingType OF
 >          aThing:
 >             fields for a thing
 >             |
 >          anotherThing:
 >             fields for another thing
 >             |
 >          lastThing:
 >             fields for last thing
 >       END  (* case *)
 >    END ;
 > 
 > Maybe I just misunderstood your problem, but using the above definition, 
 > one copy of the "List" module would handle three widely different types of 
 > things.

Um, gee.  But if you wanted to add a few more things you'd have to rewrite the   
CASE variants statement and recompile lots and lots, maybe.  And change the   
CASE statements that would litter the code too.



--  
uucp: uunet!m2xenix!puddle!5!494!4.101!Pat.Terry
Internet: Pat.Terry@p101.f4.n494.z5.fidonet.org

mbenveni@irisa.fr (Marc Benveniste) (08/15/90)

From vn Fri Aug  3 09:26:38 1990
Subject: Re: Implementing Abstract Lists
Newsgroups: comp.lang.modula2
References: <3275@rwthinf.UUCP>

From article <3275@rwthinf.UUCP>, by jubo@rwthinf.UUCP (Juergen Boerstler):
> I cannot see where this approach relies on the (relatively) strong typing
> of Modula-2, nor is it very portable (if at all). The following list of
> problems can be stated:
> 
> (1) List elements have to be passed per 'ADDRESS' (-> limited type checking,
>     because all pointers (and CARDINAL usually) are compatible with it).

 You should notice that the vulnerable operation on a list is the creation
one where the user may cheat passing a dummy address and a dummier size.
 If the user relies on the following protocol to initialise its lists,
type checking is assured from there on. Remember we don't have genericity
so it cannot be safe all the way. Please note that after creation, elements
are NOT passed per ADDRESS. They are assigned to a (typed) variable.
...
 FROM SYSTEM IMPORT TSIZE, ADR;
...
 VAR IO_Port, Item : AnyType;
     MyList : List;
...
 MyList := NewList(ADR(IO_Port), TSIZE(AnyType)); (* This cannot be enforced *)
...
 IO_Port := Item;     (* Type checking is performed here *)
 Insert(MyList);
...
 
> (3) The interface is not comprehensive enough (-> limited usability, because
>     a lot of ressources are not present, e.g. 'InsertBeforeGivenElement',
>     'IsGivenElementInList', 'LengthOfList', ....).

 This is a highly subjective matter... I admit I only provide some basic
primitives. We would have to agree on what lists are. Any way, I just
wanted to show an example of an almost generic-type-safe list module.
If you have better ideas, please share them! :-)

> **************************************************************************
> *  Juergen Boerstler              *  e-mail: jubo@rwthi3.uucp            *
> *  Lehrstuhl fuer Informatik III  *                                      *
> *  Ahornstrasse 55                *  phone:  +49/ 241/ 80-7216           *
> *  D-5100 Aachen                  *                                      *
> *  West Germany                   *                                      *
> **************************************************************************

Marc Benveniste
IRISA
Campus de Beaulieu
35042 Rennes Cedex
FRANCE

jubo@rwthinf.UUCP (Juergen Boerstler) (08/15/90)

Peter.M..Perchansky@f101.n273.z1.fidonet.org (Peter M. Perchansky) writes:

>Hello:

>    In a few days I will post my generic dequeue module to show how Modula-2 can handle generic lists.


Thank you. I got the deques-module last week. In reading the code I observed
that you too did not solve the byte/word-copying-problem in Modula-2. As most
other programmers do (including myself) some non Modula-2 call is used to do
this work (here: '_Move').
Nevertheless you can do something similar to:
      PROCEDURE ByteCopy( Destination, Source: ADDRESS; Length: CARDINAL);
         (* copies 'Length' bytes from 'Source^' to 'Destination^', using *)
	 (* the possibitlity to copy word per word, which is "standard"-  *)
	 (* Modula-2 (i.e. by Wirth in his 3rd Ed. of the language report)*)
	 (* PreCondition: Your must know how much bytes per word you have *)
	 (*               (maybe your 'SYSTEM' module supports something  *)
	 (*               like 'BYTESPERWORD' which adds to portability)  *)
	 (* CAUTION: Operation temporarily violates storage contents      *)
      VAR
         Dest, Src, TmpAddress: ADDRESS;
	 TmpWord: WORD;
	 Count, Rest: CARDINAL;

      BEGIN
	 Dest := Destination;
	 Src := Source;
	 Rest := Length MOD BYTESPERWORD;
	 (* for 'Rest <> 0' or 'Length < BYTESPERWORD' some special cases *)
	 (* are needed                                                    *)

	 IF Length > BYTESPERWORD THEN
	    FOR Count := 1 TO Length DIV BYTESPERWORD DO
	       (* copy whole words *)
	       Dest^ := Src^;
	       INC( Dest, BYTESPERWORD); INC( Src, BYTESPERWORD)
	    END;

	    (* special case for additional bytes: *)
	    IF Rest > 0 THEN
	       (* readjust start address for last word copy *)
	       DEC( Dest, BYTESPERWORD - Rest); DEC( Src, BYTESPERWORD - Rest);
	       (* copy last word *)
	       Dest^ := Src^
	    END
	 
	 ELSE
	    (* special case for 'Length < BYTESPERWORD': *)
	    TmpAddress := Dest + Rest;
	    TmpWord := TmpAddress^;
	    (* write whole word, and maybe overwrite some bytes *)
	    Dest^ := Src^;
	    (* restore the overwrited bytes *)
	    TmpAddress^ := TmpWord
	 END
      END ByteCopy;
      (* this version is not checked very well, because I couldn't copy *)
      (* the source directly, so I may have introduced some errors      *)

In addition there is a problem in comparing the contents of two list elements.
In general it is not very time efficient to perform a byte per byte test for
("user") types like:
      UserTypeForListElements = RECORD
         Key: SomeType;
         (*
         a lot of additional fields
         *)
      END;
where the relations '=', '<', '>', ... can be computed very efficiently by
user supported procedures.
Therefore generic ADTs should allow such procedures as parameters.
In addition I recommend the reading of:
   C. Lins: The Modula-2 Software Component Library, Springer-Verlag.
   SIGPlan Notices
   Journal of Ada, Pascal, & Modula-2

jubo
**************************************************************************
*  Juergen Boerstler              *  e-mail: jubo@rwthi3.uucp            *
*  Lehrstuhl fuer Informatik III  *  phone:  +49/ 241/ 80-7216           *
*  Ahornstrasse 55                *                                      *
*  D-5100 Aachen                  *                                      *
*  West Germany                   *                                      *
**************************************************************************

Chip.Richards@p3.f18.n114.z1.fidonet.org (Chip Richards) (08/16/90)

Pat,

 > Um, gee.  But if you wanted to add a few more things you'd have to rewrite 
 > the CASE variants statement and recompile lots and lots, maybe.  And change 
 > the CASE statements that would litter the code too. 

Quite right.  We do it at work *a lot*, and "we hates it"!  My little part of the world is only a quarter of a million lines, but just to re-build it, after a global include file change, takes three or four hours using four or five Apollo DN3000s.  So, we got a slow compiler.  Sue me. 

But couldn't you get yourself in much worse trouble using all the "ADR OF ARRAY OF BYTE" crap they're proposing as alternatives?  We also see a lot of *that* at work, and "hate" isn't a strong enough word for how we feel about the practice.  <grin>

Chip


--  
uucp: uunet!m2xenix!puddle!114!18.3!Chip.Richards
Internet: Chip.Richards@p3.f18.n114.z1.fidonet.org