https://gcc.gnu.org/g:99309b98c2e80a42886da36668e1e8d3d082699e

commit r14-9365-g99309b98c2e80a42886da36668e1e8d3d082699e
Author: Gaius Mulley <gaiusm...@gmail.com>
Date:   Thu Mar 7 19:41:58 2024 +0000

    PR modula2/109969 Linking large project causes an ICE
    
    This patch contains a re-write of M2LexBuf.mod which removes the linked
    list of token buckets and simplifies the implementation using a dynamic
    array.  It contains more checking (for empty source files for example).
    The patch also contains a fix for an ICE in gcc/m2/gm2-gcc/builtins.cc
    
    gcc/m2/ChangeLog:
    
            PR modula2/109969
            * gm2-compiler/M2LexBuf.def (TokenToLineNo): Rename parameter.
            (TokenToColumnNo): Rename parameter.
            (TokenToLocation): Rename parameter.
            (FindFileNameFromToken): Rename parameter.
            (DumpTokens): Rewrite comment.
            * gm2-compiler/M2LexBuf.mod: Rewrite.
            * gm2-compiler/P0SyntaxCheck.bnf (CheckInsertCandidate):
            DumpTokens before and after inserting recovery token.
            * gm2-gcc/m2builtins.cc (do_target_support_exists): Add
            bf_c99_compl case.
            * gm2-libs/Indexing.def (InitIndexTuned): New procedure
            function.
            (IsEmpty): New procedure function.
            * gm2-libs/Indexing.mod (InitIndexTuned): New procedure
            function.
            (IsEmpty): New procedure function.
            (Index): New field GrowFactor.
            (PutIndice): Use GrowFactor to extend dynamic array.
    
    Signed-off-by: Gaius Mulley <gaiusm...@gmail.com>

Diff:
---
 gcc/m2/gm2-compiler/M2LexBuf.def      |  32 +-
 gcc/m2/gm2-compiler/M2LexBuf.mod      | 810 ++++++++++++++++------------------
 gcc/m2/gm2-compiler/P0SyntaxCheck.bnf |  10 +-
 gcc/m2/gm2-gcc/m2builtins.cc          |   2 +
 gcc/m2/gm2-libs/Indexing.def          |  22 +-
 gcc/m2/gm2-libs/Indexing.mod          |  46 +-
 6 files changed, 451 insertions(+), 471 deletions(-)

diff --git a/gcc/m2/gm2-compiler/M2LexBuf.def b/gcc/m2/gm2-compiler/M2LexBuf.def
index 27610ec49dd..07f5934a631 100644
--- a/gcc/m2/gm2-compiler/M2LexBuf.def
+++ b/gcc/m2/gm2-compiler/M2LexBuf.def
@@ -1,4 +1,4 @@
-(* M2LexBuf.def provides a buffer for m2.lex.
+(* M2LexBuf.def provides a buffer for m2.flex.
 
 Copyright (C) 2001-2024 Free Software Foundation, Inc.
 Contributed by Gaius Mulley <gaius.mul...@southwales.ac.uk>.
@@ -35,18 +35,6 @@ FROM DynamicStrings IMPORT String ;
 FROM m2linemap IMPORT location_t ;
 FROM NameKey IMPORT Name ;
 
-EXPORT QUALIFIED OpenSource, CloseSource, ReInitialize, GetToken, InsertToken,
-                 InsertTokenAndRewind, GetPreviousTokenLineNo, GetLineNo,
-                 GetColumnNo, GetTokenNo, TokenToLineNo, TokenToColumnNo,
-                 TokenToLocation, GetTokenName,
-                 FindFileNameFromToken, GetFileName,
-                 ResetForNewPass,
-                 currenttoken, currentstring, currentinteger,
-                 AddTok, AddTokCharStar, AddTokInteger,
-                 MakeVirtualTok, MakeVirtual2Tok,
-                 SetFile, PushFile, PopFile,
-                 PrintTokenNo, DisplayToken, DumpTokens,
-                 BuiltinTokenNo, UnknownTokenNo ;
 
 CONST
    UnknownTokenNo = 0 ;
@@ -143,13 +131,13 @@ PROCEDURE GetTokenName (tokenno: CARDINAL) : Name ;
 
 (*
    TokenToLineNo - returns the line number of the current file for the
-                   TokenNo. The depth refers to the include depth.
+                   tokenno. The depth refers to the include depth.
                    A depth of 0 is the current file, depth of 1 is the file
                    which included the current file. Zero is returned if the
                    depth exceeds the file nesting level.
 *)
 
-PROCEDURE TokenToLineNo (TokenNo: CARDINAL; depth: CARDINAL) : CARDINAL ;
+PROCEDURE TokenToLineNo (tokenno: CARDINAL; depth: CARDINAL) : CARDINAL ;
 
 
 (*
@@ -162,31 +150,31 @@ PROCEDURE GetColumnNo () : CARDINAL ;
 
 (*
    TokenToColumnNo - returns the column number of the current file for the
-                     TokenNo. The depth refers to the include depth.
+                     tokenno. The depth refers to the include depth.
                      A depth of 0 is the current file, depth of 1 is the file
                      which included the current file. Zero is returned if the
                      depth exceeds the file nesting level.
 *)
 
-PROCEDURE TokenToColumnNo (TokenNo: CARDINAL; depth: CARDINAL) : CARDINAL ;
+PROCEDURE TokenToColumnNo (tokenno: CARDINAL; depth: CARDINAL) : CARDINAL ;
 
 
 (*
-   TokenToLocation - returns the location_t corresponding to, TokenNo.
+   TokenToLocation - returns the location_t corresponding to tokenno.
 *)
 
-PROCEDURE TokenToLocation (TokenNo: CARDINAL) : location_t ;
+PROCEDURE TokenToLocation (tokenno: CARDINAL) : location_t ;
 
 
 (*
    FindFileNameFromToken - returns the complete FileName for the appropriate
-                           source file yields the token number, TokenNo.
+                           source file yields the token number tokenno.
                            The, Depth, indicates the include level: 0..n
                            Level 0 is the current. NIL is returned if n+1
                            is requested.
 *)
 
-PROCEDURE FindFileNameFromToken (TokenNo: CARDINAL; depth: CARDINAL) : String ;
+PROCEDURE FindFileNameFromToken (tokenno: CARDINAL; depth: CARDINAL) : String ;
 
 
 (*
@@ -277,7 +265,7 @@ PROCEDURE DisplayToken (tok: toktype) ;
 
 
 (*
-   DumpTokens - developer debugging aid.
+   DumpTokens - displays all tokens.
 *)
 
 PROCEDURE DumpTokens ;
diff --git a/gcc/m2/gm2-compiler/M2LexBuf.mod b/gcc/m2/gm2-compiler/M2LexBuf.mod
index af43855e7a7..8d9b5a5a6e3 100644
--- a/gcc/m2/gm2-compiler/M2LexBuf.mod
+++ b/gcc/m2/gm2-compiler/M2LexBuf.mod
@@ -36,9 +36,16 @@ FROM NameKey IMPORT makekey ;
 FROM m2linemap IMPORT location_t, GetLocationBinary ;
 FROM M2Emit IMPORT UnknownLocation, BuiltinsLocation ;
 FROM M2Error IMPORT WarnStringAt ;
+FROM M2MetaError IMPORT MetaErrorT0 ;
+
+FROM Indexing IMPORT Index, InitIndex, GetIndice, PutIndice,
+                     KillIndex, ForeachIndiceInIndexDo,
+                     LowIndice, HighIndice, IsEmpty, InBounds,
+                     InitIndexTuned ;
+
 
 CONST
-   MaxBucketSize      = 100 ;
+   Tracing            = FALSE ;
    Debugging          = FALSE ;
    DebugRecover       = FALSE ;
    InitialSourceToken = 2 ;   (* 0 is unknown, 1 is builtin.  *)
@@ -52,7 +59,7 @@ TYPE
                               col  : CARDINAL ;
                            END ;
 
-   TokenDesc = RECORD
+   TokenDesc = POINTER TO RECORD
                   token : toktype ;
                   str   : Name ;          (* ident name or string literal.  *)
                   int   : INTEGER ;
@@ -60,61 +67,85 @@ TYPE
                   col   : CARDINAL ;
                   file  : SourceList ;
                   loc   : location_t ;
-                  insert: TokenBucket ;   (* contains any inserted tokens.  *)
+                  insert: Index ;         (* Contains any inserted tokens.  *)
                END ;
 
-   TokenBucket = POINTER TO RECORD
-                               buf : ARRAY [0..MaxBucketSize] OF TokenDesc ;
-                               len : CARDINAL ;
-                               next: TokenBucket ;
-                            END ;
-
-   ListDesc = RECORD
-                 head,
-                 tail            : TokenBucket ;
-                 LastBucketOffset: CARDINAL ;
-              END ;
-
 VAR
    CurrentSource    : SourceList ;
    UseBufferedTokens,
    CurrentUsed      : BOOLEAN ;
-   ListOfTokens     : ListDesc ;
+   ListOfTokens     : Index ;
    CurrentTokNo     : CARDINAL ;
    InsertionIndex   : CARDINAL ;
    SeenEof          : BOOLEAN ;  (* Have we seen eof since the last call
                                     to OpenSource.  *)
 
 
+(*
+   InitTokenDesc - returns a TokenDesc filled in with the parameters and
+                   the insert field set to NIL.
+*)
+
+PROCEDURE InitTokenDesc (token: toktype; str: Name; int: INTEGER;
+                         line, col: CARDINAL;
+                         file: SourceList; loc: location_t) : TokenDesc ;
+VAR
+   tokdesc: TokenDesc ;
+BEGIN
+   NEW (tokdesc) ;
+   tokdesc^.token := token ;
+   tokdesc^.str := str ;
+   tokdesc^.int := int ;
+   tokdesc^.line := line ;
+   tokdesc^.col := col ;
+   tokdesc^.file := file ;
+   tokdesc^.loc := loc ;
+   tokdesc^.insert := NIL ;
+   RETURN tokdesc
+END InitTokenDesc ;
+
+
+(*
+   DeleteTokenDesc - delete tokdesc and any sub indices.
+*)
+
+PROCEDURE DeleteTokenDesc (tokdesc: TokenDesc) ;
+BEGIN
+   IF tokdesc^.insert # NIL
+   THEN
+      ForeachIndiceInIndexDo (tokdesc^.insert, DeleteTokenDesc)
+   END ;
+   DISPOSE (tokdesc)
+END DeleteTokenDesc ;
+
+
+(*
+   Append - appends tokdesc to the end of the list defined by index.
+*)
+
+PROCEDURE Append (index: Index; tokdesc: TokenDesc) ;
+BEGIN
+   IF IsEmpty (index)
+   THEN
+      PutIndice (index, LowIndice (index), tokdesc)
+   ELSE
+      PutIndice (index, HighIndice (index) +1, tokdesc)
+   END
+END Append ;
+
+
 (*
    InitTokenList - creates an empty token list, which starts the first source 
token
-                   at position 2.  This allows position 0 to be for unknown 
location
-                   and position 1 for builtin token.
+                   at position 2.  This allows position 0 to be used for the 
unknown
+                   location and position 1 for the builtin token.
 *)
 
 PROCEDURE InitTokenList ;
 BEGIN
-   NEW (ListOfTokens.head) ;
-   ListOfTokens.tail := ListOfTokens.head ;
-   WITH ListOfTokens.tail^.buf[0] DO
-      token := eoftok ;
-      str := NulName ;
-      int := 0 ;
-      line := 0 ;
-      col := 0 ;
-      file := NIL ;
-      loc := UnknownLocation ()
-   END ;
-   WITH ListOfTokens.tail^.buf[1] DO
-      token := eoftok ;
-      str := NulName ;
-      int := 0 ;
-      line := 0 ;
-      col := 0 ;
-      file := NIL ;
-      loc := BuiltinsLocation ()
-   END ;
-   ListOfTokens.tail^.len := InitialSourceToken
+   (* 65K elements in the array and when it becomes full it will grow to 1M, 
16M etc elements.  *)
+   ListOfTokens := InitIndexTuned (0, 1024*1024 DIV 16, 16) ;
+   Append (ListOfTokens, InitTokenDesc (eoftok, NulName, 0, 0, 0, NIL, 
UnknownLocation ())) ;
+   Append (ListOfTokens, InitTokenDesc (eoftok, NulName, 0, 0, 0, NIL, 
BuiltinsLocation ()))
 END InitTokenList ;
 
 
@@ -129,8 +160,6 @@ BEGIN
    currenttoken := eoftok ;
    CurrentTokNo := InitialSourceToken ;
    CurrentSource := NIL ;
-   ListOfTokens.head := NIL ;
-   ListOfTokens.tail := NIL ;
    UseBufferedTokens := FALSE ;
    InitTokenList
 END Init ;
@@ -302,20 +331,10 @@ END KillList ;
 *)
 
 PROCEDURE ReInitialize ;
-VAR
-   s, t: TokenBucket ;
 BEGIN
-   IF ListOfTokens.head#NIL
-   THEN
-      t := ListOfTokens.head ;
-      REPEAT
-         s := t ;
-         t := t^.next ;
-         DISPOSE(s) ;
-      UNTIL t=NIL ;
-      CurrentUsed := FALSE ;
-      KillList
-   END ;
+   ForeachIndiceInIndexDo (ListOfTokens, DeleteTokenDesc) ;
+   CurrentUsed := FALSE ;
+   KillList ;
    Init
 END ReInitialize ;
 
@@ -340,6 +359,7 @@ END SetFile ;
 
 PROCEDURE OpenSource (s: String) : BOOLEAN ;
 BEGIN
+   tprintf1 ("OpenSource (%s)\n", s) ;
    SeenEof := FALSE ;
    IF UseBufferedTokens
    THEN
@@ -349,8 +369,11 @@ BEGIN
       IF m2flex.OpenSource (string (s))
       THEN
          SetFile (string (s)) ;
-         SyncOpenWithBuffer ;
          GetToken ;
+         IF IsLastTokenEof ()
+         THEN
+            MetaErrorT0 (GetTokenNo (), "source file is empty")
+         END ;
          RETURN TRUE
       ELSE
          RETURN FALSE
@@ -365,6 +388,7 @@ END OpenSource ;
 
 PROCEDURE CloseSource ;
 BEGIN
+   tprintf0 ("CloseSource\n") ;
    IF UseBufferedTokens
    THEN
       WHILE currenttoken#eoftok DO
@@ -483,138 +507,133 @@ BEGIN
 END DisplayToken ;
 
 
+VAR
+   indent: CARDINAL ;
+
+
 (*
-   UpdateFromBucket - updates the global variables:  currenttoken,
-                      currentstring, currentcolumn and currentinteger
-                      from TokenBucket, b, and, offset.
+   DumpToken -
 *)
 
-PROCEDURE UpdateFromBucket (b: TokenBucket; offset: CARDINAL) ;
+PROCEDURE DumpToken (tokdesc: TokenDesc) ;
+VAR
+   n: CARDINAL ;
 BEGIN
-   IF InsertionIndex > 0
-   THEN
-      (* we have an inserted token to use.  *)
-      Assert (b^.buf[offset].insert # NIL) ;
-      WITH b^.buf[offset].insert^.buf[InsertionIndex] DO
-         currenttoken   := token ;
-         currentstring  := KeyToCharStar(str) ;
-         currentcolumn  := col ;
-         currentinteger := int ;
-         IF Debugging
-         THEN
-            printf3('line %d (# %d  %d) ', line, offset, CurrentTokNo)
-         END
+   n := indent ;
+   WHILE n > 0 DO
+      printf0 (" ") ;
+      DEC (n)
+   END ;
+   WITH tokdesc^ DO
+      DisplayToken (token) ;
+      IF str # NulName
+      THEN
+         printf1 (" %a", str)
       END ;
-      INC (InsertionIndex) ;
-      IF InsertionIndex = b^.buf[offset].insert^.len
+      IF insert # NIL
       THEN
-         InsertionIndex := 0 ;  (* finished consuming the inserted tokens.  *)
-         INC (CurrentTokNo)
+         printf0 ("inserted error recovery tokens\n") ;
+         INC (indent, 2) ;
+         ForeachIndiceInIndexDo (insert, DumpToken) ;
+         DEC (indent, 2)
       END
-   ELSIF (b^.buf[offset].insert # NIL) AND (InsertionIndex = 0)
+   END
+END DumpToken ;
+
+
+(*
+   DumpTokens - displays all tokens.
+*)
+
+PROCEDURE DumpTokens ;
+VAR
+   high,
+   ind : CARDINAL ;
+BEGIN
+   IF IsEmpty (ListOfTokens)
    THEN
-      (* this source token has extra tokens appended after it by the error 
recovery.  *)
-      Assert (b^.buf[offset].insert^.len > 0) ;  (* we must have at least one 
token.  *)
-      InsertionIndex := 1 ; (* so set the index ready for the next 
UpdateFromBucket.  *)
-      (* and read the original token.  *)
-      WITH b^.buf[offset] DO
-         currenttoken   := token ;
-         currentstring  := KeyToCharStar(str) ;
-         currentcolumn  := col ;
-         currentinteger := int ;
-         IF Debugging
-         THEN
-            printf3('line %d (# %d  %d) ', line, offset, CurrentTokNo)
-         END
-      END
+      printf0 ("The token buffer is empty\n")
    ELSE
-      (* no inserted tokens after this token so read it and move on.  *)
-      WITH b^.buf[offset] DO
-         currenttoken   := token ;
-         currentstring  := KeyToCharStar(str) ;
-         currentcolumn  := col ;
-         currentinteger := int ;
-         IF Debugging
-         THEN
-            printf3('line %d (# %d  %d) ', line, offset, CurrentTokNo)
-         END
-      END ;
-      INC (CurrentTokNo)
+      ind := LowIndice (ListOfTokens) ;
+      high := HighIndice (ListOfTokens) ;
+      WHILE ind <= high DO
+         printf1 ("%5d ", ind) ;
+         DumpToken (GetIndice (ListOfTokens, ind)) ;
+         INC (ind)
+      END
    END
-END UpdateFromBucket ;
+END DumpTokens ;
 
 
 (*
-   DisplayTokenEntry -
+   CopyOutCurrent - copies the token in buffer[index][insertion] into
+                    then current token global variables.
 *)
 
-PROCEDURE DisplayTokenEntry (topBucket: TokenBucket; index, total: CARDINAL) ;
+PROCEDURE CopyOutCurrent (buffer: Index; index, insertion: CARDINAL) ;
 VAR
-   i: CARDINAL ;
+   tokdesc: TokenDesc ;
 BEGIN
-   printf1 ("%d: ", total) ;
-   DisplayToken (topBucket^.buf[index].token) ;
-   printf1 (" %a ", topBucket^.buf[index].str) ;
-   IF total = GetTokenNo ()
+   tokdesc := GetIndice (buffer, index) ;
+   IF insertion # 0
    THEN
-      printf0 (" <- current token")
+      tokdesc := GetIndice (tokdesc^.insert, insertion)
    END ;
-   printf0 ("\n") ;
-   (* now check for inserted tokens.  *)
-   IF topBucket^.buf[index].insert # NIL
-   THEN
-      i := 1 ;
-      WHILE i < topBucket^.buf[index].insert^.len DO
-         printf1 ("   %d: ", i) ;
-         DisplayToken (topBucket^.buf[index].insert^.buf[i].token) ;
-         printf1 (" %a\n", topBucket^.buf[index].insert^.buf[i].str) ;
-         INC (i)
-      END
+   WITH tokdesc^ DO
+      currenttoken   := token ;
+      currentstring  := KeyToCharStar (str) ;
+      currentcolumn  := col ;
+      currentinteger := int
    END
-END DisplayTokenEntry ;
+END CopyOutCurrent ;
 
 
 (*
-   DumpTokens - developer debugging aid.
+   UpdateToken - update the global current token variables from buffer[index]
+                 using inserted tokens if directed by InsertionIndex.
 *)
 
-PROCEDURE DumpTokens ;
+PROCEDURE UpdateToken (buffer: Index; index: CARDINAL) ;
 VAR
-   tb    : TokenBucket ;
-   i,
-   tokenNo,
-   total,
-   length : CARDINAL ;
+   tokdesc: TokenDesc ;
 BEGIN
-   tokenNo := GetTokenNo () ;
-   tb := ListOfTokens.head ;
-   total := 0 ;
-   WHILE tb # NIL DO
-      length := tb^.len ;
-      i := 0 ;
-      WHILE i < length DO
-         DisplayTokenEntry (tb, i, total) ;
-         INC (i) ;
-         INC (total)
-      END ;
-      tb := tb^.next
-   END ;
-   printf2 ("%d: tokenNo,  %d: total\n", tokenNo, total) ;
-   IF (total # 0) AND (tokenNo = total)
+   tokdesc := GetIndice (buffer, index) ;
+   IF InsertionIndex > 0
    THEN
-      printf1 ("%d: end of buffer ", total) ;
-      printf0 (" <- current token") ;
-      printf0 ("\n") ;
-   END ;
-END DumpTokens ;
+      (* We have an inserted token to use.  *)
+      Assert (tokdesc^.insert # NIL) ;
+      CopyOutCurrent (buffer, index, InsertionIndex) ;
+      (* Move InsertionIndex to the next position.  *)
+      INC (InsertionIndex) ;
+      IF InsertionIndex > HighIndice (tokdesc^.insert)
+      THEN
+         (* We are done consuming the inserted tokens, so move
+            onto the next original source token.  *)
+         InsertionIndex := 0 ;
+         INC (CurrentTokNo)
+      END
+   ELSIF (tokdesc^.insert # NIL) AND (InsertionIndex = 0)
+   THEN
+      (* This source token has extra tokens appended after it by the error 
recovery.
+         Set the index ready for the next UpdateToken which will read the extra
+         tokens.  *)
+      InsertionIndex := 1 ;
+      (* However this call must read the original token.  *)
+      CopyOutCurrent (buffer, index, 0)
+   ELSE
+      CopyOutCurrent (buffer, index, 0) ;
+      (* Move onto the next original source token.  *)
+      INC (CurrentTokNo)
+   END
+END UpdateToken ;
 
 
 (*
-   GetNonEofToken - providing that we have not already seen an eof for this 
source
-                    file call m2flex.GetToken and GetToken if requested.
+   GetTokenFiltered - providing that we have not already seen an eof for this 
source
+                      file call m2flex.GetToken and GetToken if requested.
 *)
 
-PROCEDURE GetNonEofToken (callGetToken: BOOLEAN) ;
+PROCEDURE GetTokenFiltered (callGetToken: BOOLEAN) ;
 BEGIN
    IF SeenEof
    THEN
@@ -627,7 +646,7 @@ BEGIN
          GetToken
       END
    END
-END GetNonEofToken ;
+END GetTokenFiltered ;
 
 
 (*
@@ -635,134 +654,95 @@ END GetNonEofToken ;
 *)
 
 PROCEDURE GetToken ;
-VAR
-   t: CARDINAL ;
-   b: TokenBucket ;
 BEGIN
    IF UseBufferedTokens
    THEN
-      t := CurrentTokNo ;
-      b := FindTokenBucket(t) ;
-      UpdateFromBucket (b, t)
+      UpdateToken (ListOfTokens, CurrentTokNo)
    ELSE
-      IF ListOfTokens.tail=NIL
+      IF NOT InBounds (ListOfTokens, CurrentTokNo)
       THEN
-         GetNonEofToken (FALSE) ;
-         IF ListOfTokens.tail=NIL
-         THEN
-            HALT
-         END
+         GetTokenFiltered (FALSE)
       END ;
-      IF CurrentTokNo>=ListOfTokens.LastBucketOffset
-      THEN
-         (* CurrentTokNo is in the last bucket or needs to be read.  *)
-         IF CurrentTokNo-ListOfTokens.LastBucketOffset<ListOfTokens.tail^.len
-         THEN
-            UpdateFromBucket (ListOfTokens.tail,
-                              CurrentTokNo-ListOfTokens.LastBucketOffset)
-         ELSE
-            (* and call ourselves again to collect the token from bucket *)
-            GetNonEofToken (TRUE)
-         END
-      ELSE
-         t := CurrentTokNo ;
-         b := FindTokenBucket (t) ;
-         UpdateFromBucket (b, t)
-      END
+      UpdateToken (ListOfTokens, CurrentTokNo)
    END
 END GetToken ;
 
 
 (*
-   SyncOpenWithBuffer - synchronise the buffer with the start of a file.
-                        Skips all the tokens to do with the previous file.
+   AppendInsertToken -
 *)
 
-PROCEDURE SyncOpenWithBuffer ;
+PROCEDURE AppendInsertToken (index: Index; tokdesc: TokenDesc) ;
 BEGIN
-   IF ListOfTokens.tail#NIL
+   IF IsEmpty (index)
    THEN
-      WITH ListOfTokens.tail^ DO
-         CurrentTokNo := ListOfTokens.LastBucketOffset+len
-      END
+      PutIndice (index, LowIndice (index), tokdesc)
+   ELSE
+      PutIndice (index, HighIndice (index) +1, tokdesc)
    END
-END SyncOpenWithBuffer ;
+END AppendInsertToken ;
 
 
 (*
-   GetInsertBucket - returns the insertion bucket associated with token count
-                     and the topBucket.  It creates a new TokenBucket if 
necessary.
+   DupTok - duplicate tokdesc and replaces the token field with token.
 *)
 
-PROCEDURE GetInsertBucket (topBucket: TokenBucket; count: CARDINAL) : 
TokenBucket ;
-BEGIN
-   IF topBucket^.buf[count].insert = NIL
-   THEN
-      NEW (topBucket^.buf[count].insert) ;
-      topBucket^.buf[count].insert^.buf[0] := topBucket^.buf[count] ;
-      topBucket^.buf[count].insert^.buf[0].insert := NIL ;
-      topBucket^.buf[count].insert^.len := 1  (* empty, slot 0 contains the 
original token for ease.  *)
-   END ;
-   RETURN topBucket^.buf[count].insert
-END GetInsertBucket ;
-
-
-(*
-   AppendToken - appends desc to the end of the insertionBucket.
-*)
-
-PROCEDURE AppendToken (insertionBucket: TokenBucket; desc: TokenDesc) ;
+PROCEDURE DupTok (tokdesc: TokenDesc; token: toktype) : TokenDesc ;
+VAR
+   dup: TokenDesc ;
 BEGIN
-   IF insertionBucket^.len < MaxBucketSize
-   THEN
-      insertionBucket^.buf[insertionBucket^.len] := desc ;
-      INC (insertionBucket^.len)
-   END
-END AppendToken ;
+   NEW (dup) ;
+   Assert (dup # NIL) ;
+   dup^ := tokdesc^ ;
+   dup^.token := token ;
+   RETURN dup
+END DupTok ;
 
 
 (*
-   InsertToken - inserts a symbol, token, infront of the current token
+   InsertToken - inserts a symbol token infront of the current token
                  ready for the next pass.
 *)
 
 PROCEDURE InsertToken (token: toktype) ;
 VAR
-   topBucket, insertionBucket: TokenBucket ;
-   count : CARDINAL ;
-   desc  : TokenDesc ;
+   prev   : CARDINAL ;
+   tokdesc: TokenDesc ;
 BEGIN
-   Assert (ListOfTokens.tail # NIL) ;
-   count := GetTokenNo () -1 ;
-   topBucket := FindTokenBucket (count) ;
-   insertionBucket := GetInsertBucket (topBucket, count) ;
-   desc := topBucket^.buf[count] ;
-   desc.token := token ;
-   desc.insert := NIL ;
-   AppendToken (insertionBucket, desc) ;
-   IF DebugRecover
+   Assert (ListOfTokens # NIL) ;
+   Assert (NOT IsEmpty (ListOfTokens)) ;
+   prev := GetTokenNo () -1 ;
+   tokdesc := GetIndice (ListOfTokens, prev) ;
+   IF tokdesc^.insert = NIL
    THEN
-      DumpTokens
-   END
+      tokdesc^.insert := InitIndex (1)
+   END ;
+   AppendInsertToken (tokdesc^.insert, DupTok (tokdesc, token))
 END InsertToken ;
 
 
 (*
-   InsertTokenAndRewind - inserts a symbol, token, infront of the current token
-                          and then moves the token stream back onto the 
inserted token.
+   InsertTokenAndRewind - inserts a symbol token infront of the current token
+                          and then moves the token stream back onto the 
inserted
+                          token.
 *)
 
 PROCEDURE InsertTokenAndRewind (token: toktype) ;
 VAR
-   offset   : CARDINAL ;
-   topBucket: TokenBucket ;
+   position : CARDINAL ;
+   tokdesc  : TokenDesc ;
 BEGIN
    IF GetTokenNo () > 0
    THEN
       InsertToken (token) ;
-      offset := CurrentTokNo -2 ;
-      topBucket := FindTokenBucket (offset) ;
-      InsertionIndex := topBucket^.buf[offset].insert^.len -1 ;
+      position := CurrentTokNo -2 ;
+      tokdesc := GetIndice (ListOfTokens, position) ;
+      IF tokdesc^.insert = NIL
+      THEN
+         tokdesc^.insert := InitIndex (1)
+      END ;
+      AppendInsertToken (tokdesc^.insert, DupTok (tokdesc, token)) ;
+      InsertionIndex := HighIndice (tokdesc^.insert) ;
       DEC (CurrentTokNo, 2) ;
       GetToken
    END
@@ -775,14 +755,6 @@ END InsertTokenAndRewind ;
 
 PROCEDURE GetPreviousTokenLineNo () : CARDINAL ;
 BEGIN
-   (*
-   IF GetTokenNo()>0
-   THEN
-      RETURN( TokenToLineNo(GetTokenNo()-1, 0) )
-   ELSE
-      RETURN( 0 )
-   END
-      *)
    RETURN GetLineNo ()
 END GetPreviousTokenLineNo ;
 
@@ -840,158 +812,122 @@ END GetTokenNo ;
 
 PROCEDURE GetTokenName (tokenno: CARDINAL) : Name ;
 VAR
-   b: TokenBucket ;
-   n: Name ;
+   tokdesc: TokenDesc ;
+   name   : Name ;
 BEGIN
-   b := FindTokenBucket (tokenno) ;
-   IF b=NIL
+   IF InBounds (ListOfTokens, tokenno)
    THEN
-      RETURN NulName
-   ELSE
-      WITH b^.buf[tokenno] DO
-         n := tokToTok (token) ;
-        IF n=NulName
-         THEN
-            RETURN str
-         ELSE
-            RETURN n
-         END
+      tokdesc := GetIndice (ListOfTokens, tokenno) ;
+      name := tokToTok (tokdesc^.token) ;
+      IF name = NulName
+      THEN
+         RETURN tokdesc^.str
+      ELSE
+         RETURN name
       END
-   END
-END GetTokenName ;
-
-
-(*
-   FindTokenBucket - returns the TokenBucket corresponding to the TokenNo.
-*)
-
-PROCEDURE FindTokenBucket (VAR TokenNo: CARDINAL) : TokenBucket ;
-VAR
-   b: TokenBucket ;
-BEGIN
-   b := ListOfTokens.head ;
-   WHILE b#NIL DO
-      WITH b^ DO
-         IF TokenNo<len
-         THEN
-            RETURN b
-         ELSE
-            DEC (TokenNo, len)
-         END
-      END ;
-      b := b^.next
    END ;
-   RETURN NIL
-END FindTokenBucket ;
+   RETURN NulName
+END GetTokenName ;
 
 
 (*
    TokenToLineNo - returns the line number of the current file for the
-                   TokenNo. The depth refers to the include depth.
+                   tokenno. The depth refers to the include depth.
                    A depth of 0 is the current file, depth of 1 is the file
                    which included the current file. Zero is returned if the
                    depth exceeds the file nesting level.
 *)
 
-PROCEDURE TokenToLineNo (TokenNo: CARDINAL; depth: CARDINAL) : CARDINAL ;
+PROCEDURE TokenToLineNo (tokenno: CARDINAL; depth: CARDINAL) : CARDINAL ;
 VAR
-   b: TokenBucket ;
-   l: SourceList ;
-BEGIN
-   IF (TokenNo = UnknownTokenNo) OR (TokenNo = BuiltinTokenNo)
+   tokdesc: TokenDesc ;
+   level  : SourceList ;
+ BEGIN
+   IF (tokenno # UnknownTokenNo) AND (tokenno # BuiltinTokenNo)
    THEN
-      RETURN 0
-   ELSE
-      b := FindTokenBucket (TokenNo) ;
-      IF b = NIL
+      IF InBounds (ListOfTokens, tokenno)
       THEN
-         RETURN 0
-      ELSE
+         tokdesc := GetIndice (ListOfTokens, tokenno) ;
          IF depth = 0
          THEN
-            RETURN b^.buf[TokenNo].line
+            RETURN tokdesc^.line
          ELSE
-            l := b^.buf[TokenNo].file^.left ;
-            WHILE depth>0 DO
-               l := l^.left ;
-               IF l=b^.buf[TokenNo].file^.left
+            level := tokdesc^.file^.left ;
+            WHILE depth > 0 DO
+               level := level^.left ;
+               IF level = tokdesc^.file^.left
                THEN
                   RETURN 0
                END ;
                DEC (depth)
             END ;
-            RETURN l^.line
+            RETURN level^.line
          END
       END
-   END
+   END ;
+   RETURN 0
 END TokenToLineNo ;
 
 
 (*
    TokenToColumnNo - returns the column number of the current file for the
-                     TokenNo. The depth refers to the include depth.
+                     tokenno. The depth refers to the include depth.
                      A depth of 0 is the current file, depth of 1 is the file
                      which included the current file. Zero is returned if the
                      depth exceeds the file nesting level.
 *)
 
-PROCEDURE TokenToColumnNo (TokenNo: CARDINAL; depth: CARDINAL) : CARDINAL ;
+PROCEDURE TokenToColumnNo (tokenno: CARDINAL; depth: CARDINAL) : CARDINAL ;
 VAR
-   b: TokenBucket ;
-   l: SourceList ;
+   tokdesc: TokenDesc ;
+   level  : SourceList ;
 BEGIN
-   IF (TokenNo = UnknownTokenNo) OR (TokenNo = BuiltinTokenNo)
+   IF (tokenno # UnknownTokenNo) AND (tokenno # BuiltinTokenNo)
    THEN
-      RETURN 0
-   ELSE
-      b := FindTokenBucket (TokenNo) ;
-      IF b=NIL
+      IF InBounds (ListOfTokens, tokenno)
       THEN
-         RETURN 0
-      ELSE
+         tokdesc := GetIndice (ListOfTokens, tokenno) ;
          IF depth = 0
          THEN
-            RETURN b^.buf[TokenNo].col
+            RETURN tokdesc^.col
          ELSE
-            l := b^.buf[TokenNo].file^.left ;
-            WHILE depth>0 DO
-               l := l^.left ;
-               IF l=b^.buf[TokenNo].file^.left
+            level := tokdesc^.file^.left ;
+            WHILE depth > 0 DO
+               level := level^.left ;
+               IF level = tokdesc^.file^.left
                THEN
                   RETURN 0
                END ;
                DEC (depth)
             END ;
-            RETURN l^.col
+            RETURN level^.col
          END
       END
-   END
+   END ;
+   RETURN 0
 END TokenToColumnNo ;
 
 
 (*
-   TokenToLocation - returns the location_t corresponding to, TokenNo.
+   TokenToLocation - returns the location_t corresponding to tokenno.
 *)
 
-PROCEDURE TokenToLocation (TokenNo: CARDINAL) : location_t ;
+PROCEDURE TokenToLocation (tokenno: CARDINAL) : location_t ;
 VAR
-   b: TokenBucket ;
+   tokdesc: TokenDesc ;
 BEGIN
-   IF TokenNo = UnknownTokenNo
+   IF tokenno = UnknownTokenNo
    THEN
       RETURN UnknownLocation ()
-   ELSIF TokenNo = BuiltinTokenNo
+   ELSIF tokenno = BuiltinTokenNo
    THEN
       RETURN BuiltinsLocation ()
-   ELSE
-      b := FindTokenBucket (TokenNo) ;
-      IF b=NIL
-      THEN
-         RETURN UnknownLocation ()
-      ELSE
-         RETURN b^.buf[TokenNo].loc
-      END
-   END
+   ELSIF InBounds (ListOfTokens, tokenno)
+   THEN
+      tokdesc := GetIndice (ListOfTokens, tokenno) ;
+      RETURN tokdesc^.loc
+   END ;
+   RETURN UnknownLocation ()
 END TokenToLocation ;
 
 
@@ -1003,35 +939,29 @@ END TokenToLocation ;
                            is requested.
 *)
 
-PROCEDURE FindFileNameFromToken (TokenNo: CARDINAL; depth: CARDINAL) : String ;
+PROCEDURE FindFileNameFromToken (tokenno: CARDINAL; depth: CARDINAL) : String ;
 VAR
-   b: TokenBucket ;
-   l: SourceList ;
+   tokdesc: TokenDesc ;
+   level  : SourceList ;
 BEGIN
-   b := FindTokenBucket (TokenNo) ;
-   IF b=NIL
+   IF (tokenno # UnknownTokenNo) AND (tokenno # BuiltinTokenNo)
    THEN
-      RETURN NIL
-   ELSE
-      IF TokenNo = UnknownTokenNo
-      THEN
-         RETURN NIL
-      ELSIF TokenNo = BuiltinTokenNo
+      IF InBounds (ListOfTokens, tokenno)
       THEN
-         RETURN NIL
-      ELSE
-         l := b^.buf[TokenNo].file^.left ;
-         WHILE depth>0 DO
-            l := l^.left ;
-            IF l=b^.buf[TokenNo].file^.left
+         tokdesc := GetIndice (ListOfTokens, tokenno) ;
+         level := tokdesc^.file^.left ;
+         WHILE depth > 0 DO
+            level := level^.left ;
+            IF level = tokdesc^.file^.left
             THEN
                RETURN NIL
             END ;
             DEC (depth)
          END ;
-         RETURN l^.name
+         RETURN level^.name
       END
-   END
+   END ;
+   RETURN NIL
 END FindFileNameFromToken ;
 
 
@@ -1049,46 +979,12 @@ END GetFileName ;
    AddTokToList - adds a token to a dynamic list.
 *)
 
-PROCEDURE AddTokToList (t: toktype; n: Name;
-                        i: INTEGER; l: CARDINAL; c: CARDINAL;
-                        f: SourceList; location: location_t) ;
+PROCEDURE AddTokToList (token: toktype; str: Name;
+                        int: INTEGER; line: CARDINAL; col: CARDINAL;
+                        file: SourceList; location: location_t) ;
 BEGIN
-   IF ListOfTokens.head=NIL
-   THEN
-      NEW (ListOfTokens.head) ;
-      IF ListOfTokens.head=NIL
-      THEN
-         (* list error *)
-      END ;
-      ListOfTokens.tail := ListOfTokens.head ;
-      ListOfTokens.tail^.len := 0
-   ELSIF ListOfTokens.tail^.len=MaxBucketSize
-   THEN
-      Assert(ListOfTokens.tail^.next=NIL) ;
-      NEW (ListOfTokens.tail^.next) ;
-      IF ListOfTokens.tail^.next=NIL
-      THEN
-         (* list error *)
-      ELSE
-         ListOfTokens.tail := ListOfTokens.tail^.next ;
-         ListOfTokens.tail^.len := 0
-      END ;
-      INC (ListOfTokens.LastBucketOffset, MaxBucketSize)
-   END ;
-   WITH ListOfTokens.tail^ DO
-      next := NIL ;
-      WITH buf[len] DO
-         token  := t ;
-         str    := n ;
-         int    := i ;
-         line   := l ;
-         col    := c ;
-         file   := f ;
-         loc    := location ;
-         insert := NIL ;
-      END ;
-      INC (len)
-   END
+   Append (ListOfTokens, InitTokenDesc (token, str, int, line,
+                                        col, file, location))
 END AddTokToList ;
 
 
@@ -1098,29 +994,15 @@ END AddTokToList ;
 
 PROCEDURE IsLastTokenEof () : BOOLEAN ;
 VAR
-   b: TokenBucket ;
+   tokdesc: TokenDesc ;
 BEGIN
-   IF ListOfTokens.tail#NIL
+   IF IsEmpty (ListOfTokens)
    THEN
-      IF ListOfTokens.tail^.len=0
-      THEN
-         b := ListOfTokens.head ;
-         IF b=ListOfTokens.tail
-         THEN
-            RETURN FALSE
-         END ;
-         WHILE b^.next#ListOfTokens.tail DO
-            b := b^.next
-         END ;
-      ELSE
-         b := ListOfTokens.tail
-      END ;
-      WITH b^ DO
-         Assert (len>0) ;     (* len should always be >0 *)
-         RETURN buf[len-1].token=eoftok
-      END
-   END ;
-   RETURN FALSE
+      RETURN FALSE
+   ELSE
+      tokdesc := GetIndice (ListOfTokens, HighIndice (ListOfTokens)) ;
+      RETURN tokdesc^.token = eoftok
+   END
 END IsLastTokenEof ;
 
 
@@ -1159,25 +1041,27 @@ END isSrcToken ;
 
 PROCEDURE MakeVirtualTok (caret, left, right: CARDINAL) : CARDINAL ;
 VAR
-   bufLeft, bufRight: TokenBucket ;
-   lc, ll, lr       : location_t ;
+   descLeft, descRight: TokenDesc ;
+   lc, ll, lr         : location_t ;
 BEGIN
    IF isSrcToken (caret) AND isSrcToken (left) AND isSrcToken (right)
    THEN
       lc := TokenToLocation (caret) ;
       ll := TokenToLocation (left) ;
       lr := TokenToLocation (right) ;
-      bufLeft := FindTokenBucket (left) ;   (* left maybe changed now.  *)
-      bufRight := FindTokenBucket (right) ;  (* right maybe changed now.  *)
-
-      IF (bufLeft^.buf[left].line = bufRight^.buf[right].line) AND
-         (bufLeft^.buf[left].file = bufRight^.buf[right].file)
+      IF InBounds (ListOfTokens, left) AND InBounds (ListOfTokens, right)
       THEN
-         (* on the same line, create a new token and location.  *)
-         AddTokToList (virtualrangetok, NulName, 0,
-                       bufLeft^.buf[left].line, bufLeft^.buf[left].col, 
bufLeft^.buf[left].file,
-                       GetLocationBinary (lc, ll, lr)) ;
-         RETURN ListOfTokens.LastBucketOffset + ListOfTokens.tail^.len - 1
+         descLeft := GetIndice (ListOfTokens, left) ;
+         descRight := GetIndice (ListOfTokens, right) ;
+         IF (descLeft^.line = descRight^.line) AND
+            (descLeft^.file = descRight^.file)
+         THEN
+            (* On the same line, create a new token and location.  *)
+            AddTokToList (virtualrangetok, NulName, 0,
+                          descLeft^.line, descLeft^.col, descLeft^.file,
+                          GetLocationBinary (lc, ll, lr)) ;
+            RETURN HighIndice (ListOfTokens)
+         END
       END
    END ;
    RETURN caret
@@ -1195,6 +1079,32 @@ BEGIN
 END MakeVirtual2Tok ;
 
 
+(*
+   tprintf0 -
+*)
+
+PROCEDURE tprintf0 (format: ARRAY OF CHAR) ;
+BEGIN
+   IF Tracing
+   THEN
+      printf0 (format)
+   END
+END tprintf0 ;
+
+
+(*
+   tprintf1 -
+*)
+
+PROCEDURE tprintf1 (format: ARRAY OF CHAR; str: String) ;
+BEGIN
+   IF Tracing
+   THEN
+      printf1 (format, str)
+   END
+END tprintf1 ;
+
+
 (* ***********************************************************************
  *
  * These functions allow m2.flex to deliver tokens into the buffer
@@ -1209,12 +1119,24 @@ PROCEDURE AddTok (t: toktype) ;
 VAR
    s: String ;
 BEGIN
-   IF t = eoftok
+   IF Tracing
    THEN
-      SeenEof := TRUE
+      printf0 (" m2.flex -> AddTok ") ;
+      DisplayToken (t) ;
+      printf0 ("\n") ;
    END ;
-   IF NOT ((t=eoftok) AND IsLastTokenEof())
+   IF (t=eoftok) AND SeenEof
    THEN
+      IF Debugging
+      THEN
+         printf0 ("extra eoftok ignored as buffer already contains eoftok\n")
+      END
+   ELSE
+      IF Debugging
+      THEN
+         printf0 ("adding token: ") ; DisplayToken (t) ;
+         printf0 ("\n")
+      END ;
       AddTokToList(t, NulName, 0,
                    m2flex.GetLineNo(), m2flex.GetColumnNo(), CurrentSource,
                    m2flex.GetLocation()) ;
@@ -1224,6 +1146,10 @@ BEGIN
          (* display each token as a warning.  *)
          s := InitStringCharStar (KeyToCharStar (GetTokenName (GetTokenNo 
()))) ;
          WarnStringAt (s, GetTokenNo ())
+      END ;
+      IF t = eoftok
+      THEN
+         SeenEof := TRUE
       END
    END
 END AddTok ;
@@ -1235,7 +1161,22 @@ END AddTok ;
 *)
 
 PROCEDURE AddTokCharStar (t: toktype; s: ADDRESS) ;
+VAR
+   str: String ;
 BEGIN
+   Assert (t # eoftok) ;
+   IF Tracing
+   THEN
+      printf0 (" m2.flex -> AddTokCharStar ") ;
+      DisplayToken (t) ;
+      str := InitStringCharStar (s) ;
+      printf1 (" %s\n", str) ;
+      str := KillString (str)
+   END ;
+   IF Debugging
+   THEN
+      printf0 ("AddTokCharStar: ") ; DisplayToken (t) ; printf0 ("\n")
+   END ;
    AddTokToList(t, makekey(s), 0, m2flex.GetLineNo(),
                 m2flex.GetColumnNo(), CurrentSource, m2flex.GetLocation()) ;
    CurrentUsed := TRUE
@@ -1252,6 +1193,13 @@ VAR
    c,
    l: CARDINAL ;
 BEGIN
+   Assert (t # eoftok) ;
+   IF Tracing
+   THEN
+      printf0 (" m2.flex -> AddTokInteger ") ;
+      DisplayToken (t) ;
+      printf1 (" %d\n", i) ;
+   END ;
    l := m2flex.GetLineNo() ;
    c := m2flex.GetColumnNo() ;
    s := Sprintf1(Mark(InitString('%d')), i) ;
diff --git a/gcc/m2/gm2-compiler/P0SyntaxCheck.bnf 
b/gcc/m2/gm2-compiler/P0SyntaxCheck.bnf
index 918b127bac6..c1c86c1827d 100644
--- a/gcc/m2/gm2-compiler/P0SyntaxCheck.bnf
+++ b/gcc/m2/gm2-compiler/P0SyntaxCheck.bnf
@@ -253,12 +253,14 @@ BEGIN
          IF DebugRecover
          THEN
             printf0 ('buffer before\n') ;
-            DumpTokens ;
-            printf0 ('inserting token: buffer after\n') ;
-            DumpTokens ;
-            printf0 ('inserting token\n')
+            DumpTokens
          END ;
          InsertTokenAndRewind (t) ;
+         IF DebugRecover
+         THEN
+            printf0 ('inserting token: buffer after insertion\n') ;
+            DumpTokens
+         END ;
          RETURN TRUE
       END
    END ;
diff --git a/gcc/m2/gm2-gcc/m2builtins.cc b/gcc/m2/gm2-gcc/m2builtins.cc
index 98d8abf8b0d..e4fc6a50c1c 100644
--- a/gcc/m2/gm2-gcc/m2builtins.cc
+++ b/gcc/m2/gm2-gcc/m2builtins.cc
@@ -871,6 +871,8 @@ do_target_support_exists (struct builtin_function_entry *fe)
       return targetm.libc_has_function (function_c99_misc, type);
     case bf_extension_lib_floatn:
       return true;
+    case bf_c99_compl:
+      return targetm.libc_has_function (function_c99_math_complex, type);
     default:
       gcc_unreachable ();
     }
diff --git a/gcc/m2/gm2-libs/Indexing.def b/gcc/m2/gm2-libs/Indexing.def
index 8aad985e84d..f7c4676df33 100644
--- a/gcc/m2/gm2-libs/Indexing.def
+++ b/gcc/m2/gm2-libs/Indexing.def
@@ -27,16 +27,23 @@ see the files COPYING3 and COPYING.RUNTIME respectively.  
If not, see
 DEFINITION MODULE Indexing ;
 
 FROM SYSTEM IMPORT ADDRESS ;
-EXPORT QUALIFIED Index, InitIndex, KillIndex, GetIndice, PutIndice,
-                 HighIndice, LowIndice, InBounds, IsIndiceInIndex,
-                 RemoveIndiceFromIndex, IncludeIndiceIntoIndex,
-                 ForeachIndiceInIndexDo, DeleteIndice, DebugIndex ;
+
 
 TYPE
    Index ;
    IndexProcedure = PROCEDURE (ADDRESS) ;
 
 
+(*
+   InitIndexTuned - creates a dynamic array with low indice.
+                    minsize is the initial number of elements the
+                    array is allocated and growfactor determines how
+                    it will be resized once it becomes full.
+*)
+
+PROCEDURE InitIndexTuned (low, minsize, growfactor: CARDINAL) : Index ;
+
+
 (*
    InitIndex - creates and returns an Index.
 *)
@@ -130,4 +137,11 @@ PROCEDURE IncludeIndiceIntoIndex (i: Index; a: ADDRESS) ;
 PROCEDURE ForeachIndiceInIndexDo (i: Index; p: IndexProcedure) ;
 
 
+(*
+   IsEmpty - return TRUE if the array has no entries it.
+*)
+
+PROCEDURE IsEmpty (i: Index) : BOOLEAN ;
+
+
 END Indexing.
diff --git a/gcc/m2/gm2-libs/Indexing.mod b/gcc/m2/gm2-libs/Indexing.mod
index f2b4b36ed70..08af13484d0 100644
--- a/gcc/m2/gm2-libs/Indexing.mod
+++ b/gcc/m2/gm2-libs/Indexing.mod
@@ -31,7 +31,8 @@ FROM Storage IMPORT ALLOCATE, REALLOCATE, DEALLOCATE ;
 FROM SYSTEM IMPORT TSIZE, WORD, BYTE ;
 
 CONST
-   MinSize = 128 ;
+   MinSize           = 128 ;
+   DefaultGrowFactor = 2 ;
 
 TYPE
    PtrToAddress = POINTER TO ADDRESS ;
@@ -45,28 +46,43 @@ TYPE
                          High      : CARDINAL ;
                          Debug     : BOOLEAN ;
                          Map       : BITSET ;
+                         GrowFactor: CARDINAL ;
                       END ;
 
 (*
-   InitIndex - creates and returns an Index.
+   InitIndexTuned - creates a dynamic array with low indice.
+                    The minsize is the initial number of elements the
+                    array is allocated and growfactor determines how
+                    it will be resized once it becomes full.
 *)
 
-PROCEDURE InitIndex (low: CARDINAL) : Index ;
+PROCEDURE InitIndexTuned (low, minsize, growfactor: CARDINAL) : Index ;
 VAR
    i: Index ;
 BEGIN
-   NEW(i) ;
+   NEW (i) ;
    WITH i^ DO
       Low := low ;
       High := 0 ;
-      ArraySize := MinSize ;
-      ALLOCATE(ArrayStart, MinSize) ;
-      ArrayStart := memset(ArrayStart, 0, ArraySize) ;
+      ArraySize := minsize * TSIZE (ADDRESS) ;
+      ALLOCATE (ArrayStart, ArraySize) ;
+      ArrayStart := memset (ArrayStart, 0, ArraySize) ;
       Debug := FALSE ;
       Used := 0 ;
-      Map := BITSET{}
+      Map := BITSET {} ;
+      GrowFactor := growfactor
    END ;
-   RETURN( i )
+   RETURN i
+END InitIndexTuned ;
+
+
+(*
+   InitIndex - creates and returns an Index.
+*)
+
+PROCEDURE InitIndex (low: CARDINAL) : Index ;
+BEGIN
+   RETURN InitIndexTuned (low, MinSize, DefaultGrowFactor)
 END InitIndex ;
 
 
@@ -162,7 +178,7 @@ BEGIN
          ELSE
             oldSize := ArraySize ;
             WHILE (n-Low)*TSIZE(ADDRESS)>=ArraySize DO
-               ArraySize := ArraySize * 2
+               ArraySize := ArraySize * GrowFactor
             END ;
             IF oldSize#ArraySize
             THEN
@@ -342,4 +358,14 @@ BEGIN
 END ForeachIndiceInIndexDo ;
 
 
+(*
+   IsEmpty - return TRUE if the array has no entries it.
+*)
+
+PROCEDURE IsEmpty (i: Index) : BOOLEAN ;
+BEGIN
+   RETURN i^.Used = 0
+END IsEmpty ;
+
+
 END Indexing.

Reply via email to