[comp.lang.modula2] POINTER/LINKED LIST HELP?

2hnenature@kuhub.cc.ukans.edu (03/30/91)

  I seem to have a problem with using the type POINTER with linked lists.
I have a seperate module with linked list functions such as Delete,Insert,
NewList etc., that I have written myself.  The problem is that I wish to make
these procedures as general as possible so they can be used with a variety of
programs.  Is it possible to specify a general POINTER type that can point to
any data type?  I assume it must be possible since the function NEW(x) allows x
to be a pointer to any type of data. 
 Related to this, I have a field in my linked list of RECORDS that contains a 
pointer to the next element in the linked list. The field is presently called
Link and I use this field to traverse the list:
 
eg.  WHILE Current#NIL DO
            Current:=Current^.Link...

As it stands now any linked list that wants to use these functions must have
a field called "Link."  Is there any way I could remove this limitation?  It is
handicapping, since if I want to use two different linked lists in a program I
must have a field "Link" in each list.

Am I making any sense?

  BTW I am using a VMS Modula-2 compiler. 
                                 Thanks for any help...
                                        S Pendleton

2hnenature@kuhub.cc.ukans.edu

Gerhard.Moeller@arbi.informatik.uni-oldenburg.de (Gerhard Moeller) (04/01/91)

Hi.
2hnenature@kuhub.cc.ukans.edu writes:


>  I seem to have a problem with using the type POINTER with linked lists.
>I have a seperate module with linked list functions such as Delete,Insert,
>NewList etc., that I have written myself.  The problem is that I wish to make
>these procedures as general as possible so they can be used with a variety of
>programs.  Is it possible to specify a general POINTER type that can point to
>any data type?  I assume it must be possible since the function NEW(x) allows x
>to be a pointer to any type of data. 
Yes, as far as I know, use ADDRESS. (Must be imported from SYSTEM) Then
you can do something like this:

PROCEDURE InsertElement (Root		:ADDRESS;
			 Element	:ADDRESS)	: BOOLEAN;

Now it doesn't care of what Element the Pointer points. But however yet
be warned: The internal Structure of the Elements should be at least
similar, I don't want to know what happens if you try to insert a
FIFO-List-Element into a Bayer-Tree...

> Related to this, I have a field in my linked list of RECORDS that contains a 
>pointer to the next element in the linked list. The field is presently called
>Link and I use this field to traverse the list:
> 
>eg.  WHILE Current#NIL DO
>            Current:=Current^.Link...

>As it stands now any linked list that wants to use these functions must have
>a field called "Link."  
What I said above. ;-)

>Is there any way I could remove this limitation?  It is
>handicapping, since if I want to use two different linked lists in a program I
>must have a field "Link" in each list.
Tricky. (As I'm not a Modula-Guru, I really have to think now for a
while. Imagine me walking all around the room and drinking coffee...)
Well, I would assume the following:
Create an opake Type ElementLink that contains a variant Record for e.g.
single lists, double, Trees, B-Trees, and whatever you like. Any Element
you create has now a field "next : ElementLink". But, of course, now you
can only use your own routines for accessing, creating, deleting and so
on. I hope you got me?

{ TYPE tLinkTypes	: (List, DoubleList, Tree, BTree, TwoThreeTree, ...)
  TYPE tElementLink	: RECORD
			    CASE LinkType OF tLinkType
				(* sorry, I forgot the syntax for
				variant records. Please have a look by
				your own. (It's a long time ago, I
				programmed in Modula...) *)
			    | List	: next :ADDRESS;
			    | DoubleList: next, prev :ADDRESS;
				.
				.
				.
}
>Am I making any sense?
Well, I don't even know if I was making sense, so how could I know about
you? 

>  BTW I am using a VMS Modula-2 compiler. 
>                                 Thanks for any help...
>                                        S Pendleton
I don't know that one, if it's standard, no problems...
(Except if I was tellin' bull.)

Ciao, Yours Gerhard.
("Never trust a hippy"... - Sex Pistols)
-- 

+---------------------------< principiis obsta! >---------------------------+
| Gerhard Moeller, Teichstrasse 12, 2900 Oldenburg (FRG)    [Geb. 02/21/68] |
|    inhouse: gimli!gemoe               uucp: ...(unido!)uniol!gmoeller     |
|DOMAIN: gerhard.moeller@arbi.informatik.uni-oldenburg.de                   |
|BITNET: gmoeller%arbi.informatik.uni-oldenburg.de@DOLUNI1 (106495@DOLUNI1) |
+-----------------------> the medium is the message <-----------------------+

2hnenature@kuhub.cc.ukans.edu (04/01/91)

In article <5164@uniol.UUCP>, Gerhard.Moeller@arbi.informatik.uni-oldenburg.de (Gerhard Moeller) writes:
> Hi.
> 2hnenature@kuhub.cc.ukans.edu writes:
> 
> 
>>  I seem to have a problem with using the type POINTER with linked lists.
>>I have a seperate module with linked list functions such as Delete,Insert,
>>NewList etc., that I have written myself.  The problem is that I wish to make
>>these procedures as general as possible so they can be used with a variety of
>>programs.  Is it possible to specify a general POINTER type that can point to
>>any data type?  I assume it must be possible since the function NEW(x) allows x
>>to be a pointer to any type of data. 
> Yes, as far as I know, use ADDRESS. (Must be imported from SYSTEM) Then
> you can do something like this:
> 
> PROCEDURE InsertElement (Root		:ADDRESS;
> 			 Element	:ADDRESS)	: BOOLEAN;
> 
> Now it doesn't care of what Element the Pointer points. But however yet
> be warned: The internal Structure of the Elements should be at least
> similar, I don't want to know what happens if you try to insert a
> FIFO-List-Element into a Bayer-Tree...

  OK, that makes sense, but when I try to implement it and try to access a field
of the record that for example "Root" is pointing to I get an error:

           Current:=Root^.Link
                          ^ Is not a field of a record (something like that)
           
and that makes sense too since the compiler sees "Root" as an ADDRESS type and
not as a pointer to a record. Thus the fields are not recognized, (I guess).
Also DISPOSE and NEW do not let me send an ADDRESS type as a parameter.
 Furthermore (as if you guys have nothing better to do than help me) another
error I get is:
        
          Current:=Root^.Link
          ^ Incompatible type (?)

  I get this error because the field "Link" is a pointer to a record and not an
ADDRESS type.

     Is there any way around this or should I give up? Does anybody know where
I could get some source code for linked list functions that are already
written?
   Thanks for help recieved.

> 
>> Related to this, I have a field in my linked list of RECORDS that contains a 
>>pointer to the next element in the linked list. The field is presently called
>>Link and I use this field to traverse the list:
>> 
>>eg.  WHILE Current#NIL DO
>>            Current:=Current^.Link...
> 
>>As it stands now any linked list that wants to use these functions must have
>>a field called "Link."  
> What I said above. ;-)
> 
>>Is there any way I could remove this limitation?  It is
>>handicapping, since if I want to use two different linked lists in a program I
>>must have a field "Link" in each list.
>>                                 Thanks for any help...
>>                                     S Pendleton 
> Ciao, Yours Gerhard.
> ("Never trust a hippy"... - Sex Pistols)
> -- 
> 
> +---------------------------< principiis obsta! >---------------------------+
> | Gerhard Moeller, Teichstrasse 12, 2900 Oldenburg (FRG)    [Geb. 02/21/68] |
> |    inhouse: gimli!gemoe               uucp: ...(unido!)uniol!gmoeller     |
> |DOMAIN: gerhard.moeller@arbi.informatik.uni-oldenburg.de                   |
> |BITNET: gmoeller%arbi.informatik.uni-oldenburg.de@DOLUNI1 (106495@DOLUNI1) |
> +-----------------------> the medium is the message <-----------------------+

seurer+@rchland.ibm.com (Bill Seurer) (04/02/91)

You can do what you want, but it is pretty ugly.

I am working on an example and will place it here when I have it ready. 
(It's a good challenge and will make a fine test case)

- Bill Seurer      IBM: seurer@rchland  Prodigy: CNSX71A
  Rochester, MN    Internet: seurer@rchland.vnet.ibm.com

seurer+@rchland.ibm.com (Bill Seurer) (04/02/91)

Here it is.  It's not pretty, it throws type checking to the wind
(mostly), but it works (as far as I tested it)!

Some notes:
1) This will allow you to make lists of anything.  The lists need not be
all the same type.  This is EXTREMELY dangerous.
2) I didn't test it much.  I suspect that List.Delete is not fully
functional.  Whadaya expect for less than half an hour?
3) Some compilers might not like some of the typecasting that was done.

Enjoy!

-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
Output of the test program:

2147483647
0
42
-906
906
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
DEFINITION MODULE List;
(* "Generic" lists module *)

FROM SYSTEM IMPORT ADDRESS, BYTE;

TYPE
  T (*Opaque type*);
  Element (*Opaque type*);

CONST
  NilList = T(NIL);
  NilElement = Element(NIL);

PROCEDURE NewList(): T;
(* Create a new list *)

PROCEDURE Insert (list: T;
                  after: Element;
                  actualElement: ARRAY OF BYTE);
(* Add a new element to a list *)

PROCEDURE Delete (list: T;
                  element: Element);
(* Delete an element from a list *)

PROCEDURE First(list: T): Element;
(* Get the first element of a list *)

PROCEDURE Next(previous: Element): Element;
(* Get the next element of a list *)

PROCEDURE Data(of: Element): ADDRESS;
(* Get the (address of the) data of an element *)

END List.
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
IMPLEMENTATION MODULE List;
(* "Generic" lists module *)

FROM SYSTEM IMPORT ADDRESS, BYTE, ADR;
FROM Storage IMPORT ALLOCATE, DEALLOCATE;

TYPE    
  T = POINTER TO ListRcd;
  Element = POINTER TO ElementRcd;

  ListRcd = RECORD
    first: Element;
  END (*ListRcd*);

  ElementRcd = RECORD
    next: Element;
    data: ADDRESS;
    dataSize: CARDINAL;
  END (*ElementRcd*);

  BytePtr = POINTER TO ARRAY[0..32767] OF BYTE;

PROCEDURE CopyBytes(from, to: BytePtr;
                    nbr: CARDINAL);
(* Ugly internal procedure to copy bytes from one address to another *)
VAR
  cnt: CARDINAL;
BEGIN
  FOR cnt := 0 TO nbr DO
    to^[cnt] := from^[cnt];
  END (*For*);
END CopyBytes;

PROCEDURE NewList(): T;
(* Create a new list *)
VAR
  newList: T;
BEGIN
  NEW(newList);
  newList^.first := NIL;
  RETURN newList;
END NewList;


PROCEDURE Insert (list: T;
                  after: Element;
                  element: ARRAY OF BYTE);
(* Add a new element to a list *)
VAR
  new: Element;
BEGIN
  NEW(new);
  new^.dataSize := HIGH(element)+1;
  ALLOCATE(new^.data, new^.dataSize);
  IF after = NIL THEN
    new^.next := list^.first;
    list^.first := new;
  ELSE
    new^.next := after^.next;
    after^.next := new;
  END (*Else*);
  CopyBytes(ADR(element), new^.data, new^.dataSize);
END Insert;

PROCEDURE Delete (list: T;
                  element: Element);
(* Delete an element from a list *)
VAR
  previous, current: Element;
BEGIN
  previous := list^.first;
  current := previous;
  LOOP
    IF current = NIL THEN
      EXIT (*Loop*);
    ELSIF current = element THEN
      IF current = list^.first THEN
        list^.first := list^.first^.next;
      ELSE
        previous^.next := current^.next;
      END (*Else*);
      DEALLOCATE(current^.data, current^.dataSize);
      DISPOSE(current);
      EXIT (*Loop*);
    ELSE
      previous := current;
      current := current^.next;
    END (*Else*);
  END (*While*);
  element := NIL;
END Delete;

PROCEDURE First(list: T): Element;
(* Get the first element of a list *)
BEGIN
  RETURN list^.first;
END First;

PROCEDURE Next(previous: Element): Element;
(* Get the next element of a list *)
BEGIN
  RETURN previous^.next;
END Next;

PROCEDURE Data(of: Element): ADDRESS;
(* Get the (address of the) data of an element *)
BEGIN
  RETURN of^.data;
END Data;

END List.
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
MODULE tryList;

IMPORT List, InOut;

TYPE
  IntPtr = POINTER TO INTEGER;

VAR
  somelist: List.T;
  el: List.Element;
  int: IntPtr;

BEGIN
  somelist := List.NewList();
  List.Insert(somelist, List.NilElement, INTEGER(906));
  (* typecast to prevent SHORTINTs from being used *)
  List.Insert(somelist, List.NilElement, INTEGER(-906));
  List.Insert(somelist, List.NilElement, INTEGER(42));
  List.Insert(somelist, List.NilElement, INTEGER(0));
  List.Insert(somelist, List.NilElement, MAX(INTEGER));

  el := List.First(somelist);
  WHILE el <> List.NilElement DO
    int := IntPtr(List.Data(el));
    InOut.WriteInt(int^, 1);
    InOut.WriteLn;
    el := List.Next(el);
  END (*While*);

  LOOP
    el := List.First(somelist);
    IF el = List.NilElement THEN
      EXIT(*Loop*);
    END (*If*);
    List.Delete(somelist, el);
  END (*Loop*);
END tryList.

- Bill Seurer      IBM: seurer@rchland  Prodigy: CNSX71A
  Rochester, MN    Internet: seurer@rchland.vnet.ibm.com

This material contains code that is supplied for illustrative purposes
only.  IBM has not tested this code via its ordinary process and it is
not supported.  IBM provides the code AS IS and specifically DISCLAIMS
ALL WARRANTIES, INCLUDING BUT NOT LIMITED TO THE IMPLIED WARRANTIES OF
MERCHANTABILITY AND FITNESS FOR PARTICULAR PURPOSE.  In no event will
IBM be responsible for any special, incidental or consequential damages,
even if advised of the possibility thereof.

If you think *I* wrote that...

warwick@cs.uq.oz.au (Warwick Allison) (04/02/91)

As a representative example, let me show you:

DEFINITION MODULE Lists;
FROM SYSTEM	IMPORT BYTE;

TYPE	List;
PROCEDURE EmptyList():List;
PROCEDURE Insert(VAR Into:List; Element:ARRAY OF BYTE);

END Lists.
-------------------
IMPLEMENTATION MODULE Lists;

FROM SYSTEM	IMPORT BYTE;
FROM Storage	IMPORT ALLOCATE;


TYPE	List=POINTER TO ListRec;
	ListRec =
		RECORD
			Data:ADDRESS;
			Size:CARDINAL;
			Next:List;
		END;

PROCEDURE EmptyList():List;
BEGIN
	RETURN NIL
END EmptyList;

PROCEDURE Insert(VAR Into:List; Element:ARRAY OF BYTE);

VAR	Head:List;
	Byte:CARDINAL;

BEGIN
	NEW(Head);
	WITH Head^ DO
		Size:=HIGH(Element)+1;
		ALLOCATE(Data,Size);
		FOR Byte:=0 TO HIGH(Element) DO
			Data[Byte]:=Element[Byte];
		END;
		Next:=Into;
	END;
	Into:=Head;
END Insert;

END Lists.

------------------------------
Okay, ignoring any syntax errors I have made, this works on most
Modula-2 compilers.  In particular, those supporting the ARRAY OF BYTE
standard.  This standard dictates that ANY type can be passed to a field
which is an ARRAY OF BYTE.

This is in no way a full complement of procedures, but it is
easy to implement the rest, once you see the basic technique.

now try...	Append, Delete, NthElement, Cardinality, IsIn, etc.

Oh, notice that these procedures are not VERY efficient, with all the
block data passing, but they work quite well, and are very generic.

Have fun,
Warwick.
--
  _--_|\   	warwick@cs.uq.oz.au
 /      *  <--	Computer Science Department,
 \_.--._/ 	University of Queensland,
       v    	AUSTRALIA.

AL281785@VMTECSLP.BITNET (RoDoGu) (04/03/91)

Here is another Lists ADT. It works (i have used for two years).
The lasts procedures (ResetList and NextList) are based on the same philosophy
as JPI Btree Toolkit.


DEFINITION MODULE Lists;

FROM SYSTEM
  IMPORT BYTE,ADDRESS;

TYPE
  List;
  NodePointer;
  PROCEDURE InitList(VAR l : List);
  PROCEDURE EmptyList(l : List):BOOLEAN;
  PROCEDURE First(l : List):NodePointer;
  PROCEDURE Last(l : List):NodePointer;
  PROCEDURE LengthList(l : List):CARDINAL;
  PROCEDURE InsertRight(VAR l : List;place : NodePointer;x : ARRAY OF BYTE);
  PROCEDURE InsertLeft(VAR l : List;place : NodePointer;x : ARRAY OF BYTE);
  PROCEDURE UpdateList(VAR l : List;place : NodePointer;x : ARRAY OF BYTE);
  PROCEDURE DeleteList(VAR l : List;VAR place : NodePointer);
  PROCEDURE Retrieve(VAR l : List;place : NodePointer; VAR x : ARRAY OF BYTE);
  PROCEDURE Next(place : NodePointer):NodePointer;
  PROCEDURE Previous(place : NodePointer):NodePointer;
  PROCEDURE EndList(place : NodePointer):BOOLEAN;
  PROCEDURE ClearList(VAR l : List);
  PROCEDURE DestroyList(VAR l : List);
  PROCEDURE ResetList(VAR l : List);
  PROCEDURE NextList(VAR l : List;VAR data : ARRAY OF BYTE) : BOOLEAN;

END Lists.

IMPLEMENTATION MODULE Lists;

FROM SYSTEM
  IMPORT ADDRESS,ADR,SIZE,BYTE;
FROM Storage
  IMPORT ALLOCATE,DEALLOCATE;

TYPE
  NodePointer = POINTER TO Node;
  List = POINTER TO
         RECORD
           Start,
           Curr,
           First,Last : NodePointer;
           len : CARDINAL
         END;
  Node = RECORD
           Info : ADDRESS;
           Mem  : CARDINAL;
           Left,Right : NodePointer
         END;

  TYPE
       PtrAdr = POINTER TO ARRAY 0..0FFFFH-1| OF BYTE;


  PROCEDURE Move(f,t : PtrAdr; (* check type compativility *)
                 c : CARDINAL);
  TYPE
       xu    : CARDINAL;
  BEGIN
    FOR xu := 0 TO c - 1 DO
      t^xu| := f^xu|
    END (* for *);
  END Move;

  PROCEDURE InitList(VAR l : List);
  BEGIN
    NEW(l);
    WITH l^ DO
      First := NIL;
      Last := NIL;
      NEW(Start);
      len := 0
    END
  END InitList;

  PROCEDURE EmptyList(l : List):BOOLEAN;
  BEGIN
    RETURN l^.First = NIL
  END EmptyList;

  PROCEDURE First(l : List):NodePointer;
  BEGIN
    RETURN l^.First
  END First;

  PROCEDURE Last(l : List):NodePointer;
  BEGIN
    RETURN l^.Last
  END Last;

  PROCEDURE LengthList(l : List):CARDINAL;
  BEGIN
    RETURN l^.len
  END LengthList;

  PROCEDURE InsertRight(VAR l : List;place : NodePointer;x : ARRAY OF BYTE);
  VAR
    t : NodePointer;
  BEGIN
    WITH l^ DO
      NEW(t);
      t^.Mem := SIZE(x);
      ALLOCATE(t^.Info,t^.Mem);
      MoveFwd(ADR(x),t^.Info,SIZE(x));
      INC(len);
      IF First = NIL THEN
        First := t;
        Last := t;
        t^.Right := NIL;
        t^.Left := NIL
      ELSIF place = Last THEN
        Last^.Right := t;
        t^.Left := Last;
        t^.Right := NIL;
        Last := t
      ELSIF place # NIL THEN
        t^.Right := place^.Right;
        t^.Left := place;
        place^.Right := t;
        t^.Right^.Left := t
      ELSE
        DEALLOCATE(t^.Info,t^.Mem);
        DISPOSE(t);
        DEC(len)
      END
    END
  END InsertRight;

  PROCEDURE InsertLeft(VAR l : List;place : NodePointer;x : ARRAY OF BYTE);
  VAR
    t : NodePointer;
  BEGIN
    WITH l^ DO
      NEW(t);
      t^.Mem := SIZE(x);
      ALLOCATE(t^.Info,t^.Mem);
      MoveFwd(ADR(x),t^.Info,SIZE(x));
      INC(len);
      IF First = NIL THEN
        First := t;
        Last := t;
        t^.Right := NIL;
        t^.Left := NIL
      ELSIF place = First THEN
        t^.Right := First;
        t^.Left := NIL;
        First^.Left := t;
        First := t
      ELSIF place # NIL THEN
        t^.Left := place^.Left;
        t^.Right := place;
        t^.Left^.Right :=  t;
        place^.Left := t
      ELSE
        DEALLOCATE(t^.Info,t^.Mem);
        DISPOSE(t);
        DEC(len)
      END
    END
  END InsertLeft;

  PROCEDURE UpdateList(VAR l : List;place : NodePointer; x : ARRAY OF BYTE);
  BEGIN
    WITH l^ DO
      IF (First # NIL) & (place # NIL) THEN
        MoveFwd(ADR(x),place^.Info,place^.Mem)
      END
    END
  END UpdateList;

  PROCEDURE DeleteList(VAR l : List;VAR place : NodePointer);
  VAR
    t : NodePointer;
  BEGIN
    WITH l^ DO
      IF First # NIL THEN
        IF place = First THEN
          t := First;
          First := First^.Right;
          place := First;
          IF First # NIL THEN First^.Left := NIL END
        ELSIF place = Last THEN
          t := Last;
          Last := Last^.Left;
          place := NIL;
          Last^.Right := NIL
        ELSIF place # NIL THEN
          t := place;
          place := place^.Right;
          t^.Right^.Left := t^.Left;
          t^.Left^.Right := t^.Right
        ELSE
          t := NIL
        END;
        IF t # NIL THEN
          DEALLOCATE(t^.Info,t^.Mem);
          DISPOSE(t);
          DEC(len)
        END
      END
    END
  END DeleteList;

  PROCEDURE Retrieve(VAR l : List;place : NodePointer; VAR x : ARRAY OF BYTE);
  BEGIN
    WITH l^ DO
      IF (First # NIL) & (place # NIL) THEN
        MoveFwd(place^.Info,ADR(x),place^.Mem)
      END
    END
  END Retrieve;

  PROCEDURE Next(place : NodePointer):NodePointer;
  BEGIN
    IF place # NIL THEN
      RETURN place^.Right
    ELSE
      RETURN NIL
    END
  END Next;

  PROCEDURE Previous(place : NodePointer):NodePointer;
  BEGIN
    IF place # NIL THEN
      RETURN place^.Left
    ELSE
      RETURN NIL
    END
  END Previous;

  PROCEDURE EndList(place : NodePointer):BOOLEAN;
  BEGIN
    RETURN place = NIL
  END EndList;

  PROCEDURE ClearList(VAR l : List);
  VAR
    trace : NodePointer;
  BEGIN
    trace := First(l);
    WHILE NOT EndList(trace) DO
      DeleteList(l,trace)
    END
  END ClearList;

  PROCEDURE DestroyList(VAR l : List);
  BEGIN
    ClearList(l);
    DISPOSE(l^.Start);
    DISPOSE(l)
   END DestroyList;

  PROCEDURE ResetList(VAR l : List);
  BEGIN
    WITH l^ DO
      Start^.Right := First;
      Start^.Left := Last;
      Curr := Start;
    END (* with *)
  END ResetList;

  PROCEDURE NextList(VAR l : List;VAR data : ARRAY OF BYTE) : BOOLEAN;
  BEGIN
    WITH l^ DO
      Curr := Next(Curr);
      IF ~ EndList(Curr) THEN
        Retrieve(l,Curr,data);
        RETURN TRUE
      ELSE
        RETURN FALSE
      END (* if *);
    END (* with *);
  END NextList;

END Lists.

MODULE Example;

(* using ResetList and NextList *);

VAR
    n : CARDINAL;
    l : List;

BEGIN

   -
   -
   -

  ResetList(l);
  WHILE NextList(l,n) DO  (* this is beautiful! *)
    WrCard(n,0);
    WrLn
  END (* while *);
END Example.


Instituto Tecnologico y de Estudios Superiores de Monterrey, Campus San Luis
ROberto DOminguez GUtierrez.

Gerhard.Moeller@arbi.informatik.uni-oldenburg.de (Gerhard Moeller) (04/03/91)

Hi again...

>In article <5164@uniol.UUCP>, Gerhard.Moeller@arbi.informatik.uni-oldenburg.de (Gerhard Moeller) writes:
>> Hi.
>> 2hnenature@kuhub.cc.ukans.edu writes:
>> 
>> 
>>>  I seem to have a problem with using the type POINTER with linked lists.
>>>I have a seperate module with linked list functions such as Delete,Insert,
>>>NewList etc., that I have written myself.  The problem is that I wish to make
>>>these procedures as general as possible so they can be used with a variety of
>>>programs.  Is it possible to specify a general POINTER type that can point to
>>>any data type?  I assume it must be possible since the function NEW(x) allows x
>>>to be a pointer to any type of data. 
>> Yes, as far as I know, use ADDRESS. (Must be imported from SYSTEM) Then
>> you can do something like this:
>> 
>> PROCEDURE InsertElement (Root		:ADDRESS;
>> 			 Element	:ADDRESS)	: BOOLEAN;
>> 
>> Now it doesn't care of what Element the Pointer points. But however yet
>> be warned: The internal Structure of the Elements should be at least
>> similar, I don't want to know what happens if you try to insert a
>> FIFO-List-Element into a Bayer-Tree...

>  OK, that makes sense, but when I try to implement it and try to access a field
>of the record that for example "Root" is pointing to I get an error:

>           Current:=Root^.Link
>                          ^ Is not a field of a record (something like that)
>           
>and that makes sense too since the compiler sees "Root" as an ADDRESS type and
>not as a pointer to a record. Thus the fields are not recognized, (I guess).
>Also DISPOSE and NEW do not let me send an ADDRESS type as a parameter.
> Furthermore (as if you guys have nothing better to do than help me) another
>error I get is:
>        
>          Current:=Root^.Link
>          ^ Incompatible type (?)

>  I get this error because the field "Link" is a pointer to a record and not an
>ADDRESS type.

>     Is there any way around this or should I give up? Does anybody know where
>I could get some source code for linked list functions that are already
>written?
>   Thanks for help recieved.

Well, before I start explaning, I'd better send a copy of source that I've
written many days ago. It sure works and should be self-explaining.
(Sometimes a sample helps more than 1000 words.)
BTW the following source implements a few useful system-calls of the UNIX 
c-library and therefore only works with Unix... have a close look at the
time-routines for example.

(* for UNIX only *)
 
FOREIGN MODULE MySysLib;

   FROM SYSTEM IMPORT ADDRESS;

   TYPE

      int	= INTEGER;
      SIGNED    = INTEGER;
      UNSIGNED  = INTEGER;
      inoT      = CARDINAL;

      offT      = INTEGER;
      devT      = SHORTINT;
      timeT     = INTEGER;

      Stat =
         RECORD
            stDev    : devT;
            stIno    : inoT;
            stMode   : SHORTCARD;
            stNlink  : SHORTINT;
            stUid    : SHORTINT;
            stGid    : SHORTINT;
            stRdev   : devT;
            stSize   : offT;
            stAtime  : timeT;
            stSpare1 : INTEGER;
            stMtime  : timeT;
            stSpare2 : INTEGER;
            stCtime  : timeT;
            stSpare3 : INTEGER;
            stBlksize: INTEGER;
            stBlocks : INTEGER;
            stSpare4 : ARRAY [0..1] OF INTEGER;
         END;

      tms =
	 RECORD
	    utime : timeT;  
	    stime : timeT;
	    cutime : timeT;
	    cstime : timeT;
	 END;

       tmtype =
	 RECORD
	    tm_sec	: int;
	    tm_min	: int;
	    tm_hour	: int;
	    tm_mday	: int;
	    tm_mon	: int;
	    tm_year	: int;
	    tm_wday	: int;
	    tm_yday	: int;
	    tm_istdst	: int;
	  END;

   CONST

      (* signals *)

         SIGHUP 	= 01;     	(* hangup *)
         SIGINT 	= 02;     	(* interrupt *)
         SIGQUIT	= 03;		(* [1] quit *)
         SIGILL 	= 04;		(* [1] illegal instruction (not reset when caught) *)
         SIGTRAP	= 05;		(* [1] trace trap (not reset when caught) *)
         SIGIOT 	= 06;		(* [1] IOT instruction *)
         SIGEMT 	= 07;		(* [1] EMT instruction *)
         SIGFPE 	= 08;		(* [1] floating point exception *)
         SIGKILL	= 09;     	(* kill (cannot be caught or ignored) *)
         SIGBUS 	= 10;		(* [1] bus error *)
         SIGSEGV	= 11;		(* [1] segmentation violation *)
         SIGSYS 	= 12;		(* [1] bad argument to system call *)
         SIGPIPE	= 13;     	(* write on a pipe with no one to read it *)
         SIGALRM	= 14;     	(* alarm clock *)
         SIGTERM	= 15;     	(* software termination signal *)
         SIGADDR	= 16;		(* [1] address error: odd address *)
         SIGZERO	= 17;		(* [1] zero divide *)
         SIGCHK 	= 18;		(* [1] check error (68000 chk instruction) *)
         SIGOVER	= 19;		(* [1] software termination signal *)
         SIGPRIV	= 20;		(* [1] software termination signal *)
         SIGUSR1	= 21;    	(* user-defined signal 1 *)
         SIGUSR2	= 22;     	(* user-defined signal 2 *)
         SIGCLD		= 23;		(* [2] death of a child *)
         SIGPWR		= 24;		(* [2] power fail *)
         SIGWINCH	= 25;		(* [2] window size changed *)
         SIGPOLL	= 26;		(* [3] selectable event pending *)

      (* flags for open *)

      oTRUNC   = 01000B;    (* open with truncation *)
      oAPPEND  =   010B;    (* append, i.e writes at the end *)
      oRDWR    =    02B;    (* open for reading and writing *)
      oWRONLY  =    01B;    (* open for writing only *)
      oRDONLY  =     0B;    (* open for reading only *)

      (* file access permisson flags (for create and umask) *)

      pXUSID   = 04000B;    (* set user ID on execution *)
      pXGRID   = 02000B;    (* set group ID on execution *)
      pSTEXT   = 01000B;    (* save text image after execution *)
      pROWNER  =  0400B;    (* read by owner *)
      pWOWNER  =  0200B;    (* write by owner *)
      pXOWNER  =  0100B;    (* execute by owner *)
      pRGROUP  =   040B;    (* read by group *)
      pWGROUP  =   020B;    (* write by group *)
      pXGROUP  =   010B;    (* execute by group *)
      pROTHERS =    04B;    (* read by others *)
      pWOTHERS =    02B;    (* write by others *)
      pXOTHERS =    01B;    (* execute by others *)
      pEMPTY   =     0B;    (* no flag set *)
    
      (* file access check flags (for access) *)
 
      cREAD    = 04H;       (* check if readable *)
      cWRITE   = 02H;       (* check if writable *)
      cEXEC    = 01H;       (* check if executable *)
      cEXISTS  =  0H;       (* check existance *)
 

   PROCEDURE umask (cmask : SIGNED) : SIGNED;

   PROCEDURE access (path  : ADDRESS; amode : SIGNED) : SIGNED;

   PROCEDURE creat (path  : ADDRESS; cmode : SIGNED) : SIGNED;

   PROCEDURE open (path : ADDRESS; oflag : SIGNED) : SIGNED;

   PROCEDURE close (fildes : SIGNED) : SIGNED;

   PROCEDURE unlink (path : ADDRESS) : SIGNED;

   PROCEDURE read (fildes : SIGNED; buf : ADDRESS; nbyte : UNSIGNED) : SIGNED;

   PROCEDURE write (fildes : SIGNED; buf : ADDRESS; nbyte : UNSIGNED) : SIGNED;

   PROCEDURE malloc (size : UNSIGNED) : ADDRESS;

   PROCEDURE free (ptr : ADDRESS);

   PROCEDURE stat (path: ADDRESS; VAR buf: Stat) : INTEGER;

   PROCEDURE fstat (fd: SIGNED  ; VAR buf: Stat) : INTEGER;

   PROCEDURE time (VAR t : INTEGER);

   PROCEDURE times (VAR buffer: tms);

   PROCEDURE localtime (clockpointer : ADDRESS) : ADDRESS;
   
   PROCEDURE system (string : ADDRESS) : SIGNED;

   PROCEDURE exit (n: INTEGER);

   PROCEDURE alarm (sec : UNSIGNED);

   PROCEDURE signal (sig :int; func :PROC);

   PROCEDURE sigset (sig :int; func :PROC);

   PROCEDURE sighold (sig :int);

   PROCEDURE sigrelse (sig :int);

   PROCEDURE sigignore (sig :int);

   PROCEDURE sigpause (sig :int);

END MySysLib.

(*============================================================================*)

IMPLEMENTATION MODULE MySysLib;
   (* implemented by C library *)
END MySysLib.

(*============================================================================*)

[...]		(* Stuff deleted *)

MODULE Editor;

(* @@
  EXPORT Edit (Filename);
*)

  FROM MyStuff		IMPORT	(* TYPE *)	StringType;
  FROM MySysLib		IMPORT	(* TYPE *)	SIGNED,
  				(* PROC *)	system;

[...]		(* Stuff deleted *)
  
  CONST	Editor		= "em ";
  	Filename	= "Test";


  PROCEDURE Edit (File :ARRAY OF CHAR);
    VAR	EditFile	: StringType;
	unixcommand	: StringType;
	unixcall	: POINTER TO StringType;
	error		: SIGNED;
  BEGIN (* Edit *)
    Concat (Editor, File, EditFile);
    ALLOCATE (unixcall, SIZE (unixcommand));
    unixcall^ := EditFile;
    error := system (unixcall);
    DEALLOCATE (unixcall, SIZE(unixcommand));
  END Edit;
  
 
BEGIN (* Editor *)
[...]		(* Stuff deleted *)
END Editor.

[...]		(* Stuff deleted *)

(*============================================================================*)

Ok??			
		Hope that helped, Gerhard.

Jon.Guthrie@p25.f506.n106.z1.fidonet.org (Jon Guthrie) (04/03/91)

 On a message of 31-Mar-91, 2hnenature@kuhub.cc.ukans.edu (1:105/42.0) Said:

 > Is it possible to specify a general POINTER type that can point to
 > any data type?  I assume it must be possible since the function
 > NEW(x) allows x to be a pointer to any type of data.

Yes, SYSTEM exports the data type ADDRESS which is assignable to (and
from) any pointer type.  (Check whatever documentation you have for
more details.)

As for the assumption that it must be possible based on the NEW()
procedure, I'd have to say that you're on thin ice.  Standard
procedures are allowed to break rules in a variety of ways, and may,
in fact, be implemented as additions to the syntax of the language
rather than as procedures.



--  
uucp: uunet!m2xenix!puddle!106!506.25!Jon.Guthrie
Internet: Jon.Guthrie@p25.f506.n106.z1.fidonet.org

Rajah.Dodger@urchin.fidonet.org (Rajah Dodger) (04/04/91)

I may be naive here (I haven't done any serious programming in three 
years) but I see no reason why you couldn't have a "generic pointer". 
What you would need to do would be to make it a pointer to some 
(arbitrarily chosen) data type that is large enough to hold the largest 
item your programs would want to point to. Then you dereference and do a 
type cast.  I can see a few problems with this, but it looks like a 
reasonable start.  The alternative option is to use pointer to CHAR, get 
the address of the item pointer to and then do your own memory magic to 
pull it up as the right type information.
 
Any way you slice it, you're going to have to do some type casting.

gkt@iitmax.iit.edu (George Thiruvathukal) (04/09/91)

In article <10726.27FA98F3@urchin.fidonet.org>, Rajah.Dodger@urchin.fidonet.org (Rajah Dodger) writes:
> I may be naive here (I haven't done any serious programming in three 
> years) but I see no reason why you couldn't have a "generic pointer". 

You are correct.  Modula-2, as defined in Programming in Modula-2, has two
data types which are "generic" in nature: WORD and ADDRESS.  These types are
defined in the SYSTEM module.

> What you would need to do would be to make it a pointer to some 
> (arbitrarily chosen) data type that is large enough to hold the largest 
> item your programs would want to point to. Then you dereference and do a 
> type cast.  I can see a few problems with this, but it looks like a 
> reasonable start.

Actually, you have a good handle on the concepts.  The generic pointer
(of type ADDRESS) is a pointer which can hold any pointer type.  It cannot
be dereferenced, however, because it is unknown at compile time what the
generic pointer points to.  In short, to actually examine what is pointed to
by a variable of type ADDRESS, one must assign the variable to a pointer to a
specific type and dereference that pointer.  You might want to contrast this
with the mechanism employed in the C language, where a "cast operator" is 
present for the purpose of explicitly changing the type of the pointer, even
if it is generic, into another pointer type.

-- 
George Thiruvathukal

Laboratory for Parallel Computing and Languages
Illinois Institute of Technology
Chicago