-- File: [Cherry]<Thyme>System>C03>spGlobalsimpl.mesa
-- Last editted by:
-- SChen, February 12, 1984  7:56 PM to support oldArgVector
-- Barth, July 11, 1983  12:19 PM
-- SChen April 19, 1983  1:45 PM
-- Wilhelm April 27, 1982  4:05 PM, reformated by Barth and stored under
--   [Cherry]<Barth>Thyme>1.97> .
-- Details at end of file.
DIRECTORY spGlobals, AltoDefs, CWF, IODefs, StreamDefs,
          StringDefs, ComLineDefs, AbsAllocDefs;
spGlobalsImpl:  PROGRAM
  IMPORTS spGlobals, CWF, StreamDefs, StringDefs, ComLineDefs,
          A:  AbsAllocDefs
  EXPORTS spGlobals =
  BEGIN
    OPEN spGlobals;

    inputFileName:  PUBLIC STRING ← [40];
    inputFile:      StreamDefs.StreamHandle;
    maxInclude:     CARDINAL = 10;
    fileStack:      ARRAY[0..maxInclude) OF StreamDefs.StreamHandle;
    fileStackTop:   CARDINAL;

    line:       STRING = [256];
    chars:      STRING = [256];
    char:       CHARACTER ← ';;
    cptr:       CARDINAL ← 0;
    genSymCtr:  CARDINAL ← 10000;

    item:       PUBLIC itemType;
    value:      PUBLIC REAL;
    newString:  PUBLIC LONG STRING;

    keyList:  ARRAY keys OF STRING ← ["node",
                                      "resistor",
                                      "capacitor",
                                      "inductor",
                                      "voltage",
                                      "current",
                                      "run",
                                      "print",
                                      "circuit",
                                      "model",
                                      "plot",
                                      "ic",
                                      "dump",
                                      "asserts",
                                      "checkpoint",
                                      "library",
                                      ""];

    initialHistory:  PUBLIC history ← [0.0, 0.0,
                                       0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0];



    makeRealThing:  PUBLIC PROCEDURE[last:  realThingPtr]
                             RETURNS[new:  realThingPtr] =
      BEGIN
        new ← A.Allocate[SIZE[realThing]];
        new↑ ← [last, TRUE, unReal[]]
      END;

    makeName:  PUBLIC PROCEDURE[last:  namePtr] RETURNS[new:  namePtr] =
      BEGIN
        new ← A.Allocate[SIZE[nameBlk]];
        new↑ ← [NIL, last, NIL, NIL, NIL, nodeName[]]
      END;

    makeConLink:  PUBLIC PROCEDURE[last:  conLinkPtr, conName:  namePtr]
                           RETURNS[new:  conLinkPtr] =
      BEGIN
        new ← A.Allocate[SIZE[conLink]];
        new↑ ← [last, conName]
      END;

    makeBranchLink:  PUBLIC PROCEDURE[last:  branchLinkPtr, b:  branchPtr,
                                      positiveNode:  BOOLEAN]
                              RETURNS[new:  branchLinkPtr] =
      BEGIN
        new ← A.Allocate[SIZE[branchLink]];
        new↑ ← [last, b, NIL, positiveNode]
      END;

    makeExpr:  PUBLIC PROCEDURE RETURNS[e:  expressionPtr] =
      BEGIN
        e ← A.Allocate[SIZE[expressionNode]];
        e↑ ← [NIL,]
      END;

    makeNode:  PUBLIC PROCEDURE RETURNS[n:  nodePtr] =
      BEGIN
        n ← A.Allocate[SIZE[node]];
        n↑ ← [NIL, NIL, NIL, NIL, NIL, NIL, NIL,
              initialHistory, FALSE, FALSE, FALSE]
      END;

    makeResistor:  PUBLIC PROCEDURE RETURNS[r:  resistorPtr] =
      BEGIN
        r ← A.Allocate[SIZE[resistor branch]];
        r↑ ← [NIL, NIL, NIL, NIL, NIL, 0.0, NIL, 0, resistor[]]
      END;

    makeCapacitor:  PUBLIC PROCEDURE RETURNS[c:  capacitorPtr] =
      BEGIN
        c ← A.Allocate[SIZE[capacitor branch]];
        c↑ ← [NIL, NIL, NIL, NIL, NIL, 0.0, NIL, 0, capacitor[NIL]]
      END;

    makeInductor:  PUBLIC PROCEDURE RETURNS[l:  inductorPtr] =
      BEGIN
        l ← A.Allocate[SIZE[inductor branch]];
        l↑ ← [NIL, NIL, NIL, NIL, NIL, 0.0, NIL, 0, 
              inductor[NIL, initialHistory]]
      END;

    makeVoltage:  PUBLIC PROCEDURE RETURNS[v:  vSourcePtr] =
      BEGIN
        v ← A.Allocate[SIZE[vSource branch]];
        v↑ ← [NIL, NIL, NIL, NIL, NIL, 0.0, NIL, 0,
              vSource[NIL, 0.0, 0.0]]
      END;

    makeCurrent:  PUBLIC PROCEDURE RETURNS[i:  iSourcePtr] =
      BEGIN
        i ← A.Allocate[SIZE[iSource branch]];
        i↑ ← [NIL, NIL, NIL, NIL, NIL, 0.0, NIL, 0, iSource[NIL]]
      END;

    makeFunction:  PUBLIC PROCEDURE RETURNS[f:  functionPtr] =
      BEGIN
        f ← A.Allocate[SIZE[fn modFuncBlk]];
        f↑ ← [NIL, NIL, NIL, NIL, NIL, fn[, NIL]]
      END;

    makeModel:  PUBLIC PROCEDURE RETURNS[m:  modelPtr] =
      BEGIN
        m ← A.Allocate[SIZE[mod modFuncBlk]];
        m↑ ← [NIL, NIL, NIL, NIL, NIL, mod[, NIL, NIL, NIL, NIL]]
      END;

    makeModBranch:  PUBLIC PROCEDURE[last:  modBrPtr, b:  branchPtr]
                             RETURNS[mb:  modBrPtr] =
      BEGIN
        mb ← A.Allocate[SIZE[modelBranch]];
        mb↑ ← [last, b]
      END;

    makeArgSource:  PUBLIC PROCEDURE[na:  CARDINAL] RETURNS[a:  argSource] =
      BEGIN
        a ← DESCRIPTOR[A.Allocate[SIZE[nodePtr]*na], na];
      END;

    makeArgNames:  PUBLIC PROCEDURE[na:  CARDINAL] RETURNS[a:  argNames] =
      BEGIN
        a ← DESCRIPTOR[A.Allocate[SIZE[namePtr]*na], na];
      END;

    makeArgList:  PUBLIC PROCEDURE[na:  CARDINAL] RETURNS[a:  argList] =
      BEGIN
        a ← DESCRIPTOR[A.Allocate[SIZE[REAL]*na], na];
      END;

    makeTreeNode:  PUBLIC PROCEDURE[inst:  cktInstNamePtr]
                            RETURNS[t: instTreePtr] =
      BEGIN
        t ← A.Allocate[SIZE[instTreeNode]];
        t↑ ← [NIL, NIL, NIL, inst, NIL, NIL]
      END;

    makeLongString:  PUBLIC PROCEDURE[len:  CARDINAL]
                              RETURNS[ls:  LONG STRING] =
      BEGIN
        ls ← A.Allocate[2 + (len + 1)/2];
        ls↑ ← [length:  0, maxlength:  len, text:]
      END;


    openInputFile:  PUBLIC PROCEDURE =
      BEGIN
        inputFile ← ComLineDefs.OpenFile[inputFileName, ".thy"];
        line.length ← 0;
        fileStackTop ← 0
      END;

    includeFile:  PROCEDURE =
      BEGIN
        fname:  STRING = [40];
        i:  CARDINAL ← 0;

        nextChar[TRUE];
        UNTIL char = IODefs.TAB OR char = IODefs.CR OR char = '  DO
          IF i = 40 THEN EXIT;
          fname[i] ← char;
          nextChar[FALSE];
          i ← i + 1
        ENDLOOP;
        fname.length ← i;
        IF fileStackTop < maxInclude THEN
          BEGIN
            ENABLE
              StreamDefs.FileNameError =>
                BEGIN
                  error[103, FALSE];
                  GOTO fileError
                END;
            fileStack[fileStackTop] ← inputFile;
            inputFile ← StreamDefs.NewByteStream[fname, StreamDefs.Read];
            fileStackTop ← fileStackTop + 1
          EXITS fileError => NULL
          END
        ELSE error[104, FALSE];
        next[]
      END;

    popIncludeFile:  PROCEDURE =
      BEGIN
        IF fileStackTop > 0 THEN
          BEGIN
            fileStackTop ← fileStackTop - 1;
            inputFile ← fileStack[fileStackTop];
            nextChar[FALSE];
            next[]
          END
        ELSE item ← eof
      END;


    newLine:  PROCEDURE =
      BEGIN
        cptr ← 0;
        line.length ← 0;
        DO
          IF inputFile.endof[inputFile] THEN char ← IODefs.ControlZ
          ELSE char ← inputFile.get[inputFile];
          line[line.length] ← char;
          line.length ← line.length + 1;
          IF char = IODefs.ControlZ OR char = IODefs.CR THEN EXIT;
        ENDLOOP;
        IF char = IODefs.ControlZ THEN
          BEGIN
            line[line.length] ← IODefs.CR;
            line.length ← line.length + 1
          END;
        CWF.WF1["%s", line]
      END;

    nextChar:  PROCEDURE[skip:  BOOLEAN] =
      BEGIN
        DO
          IF cptr >= line.length THEN newLine[];
          char ← line[cptr];
          cptr ← cptr + 1;
          IF char # '  THEN EXIT;
          IF ~skip THEN EXIT
        ENDLOOP
      END;

    scaleFactor:  PROCEDURE RETURNS[s:  INTEGER] =
      BEGIN
        s ← SELECT char FROM
              'M => 6,
              'k => 3,
              'K => 3,
              'm => -3,
              'u => -6,
              'n => -9,
              'p => -12,
            ENDCASE => 0;
        IF s # 0 THEN nextChar[FALSE];
        SELECT char FROM
          'F, 'H, 'V, 'A, 's => nextChar[TRUE]
        ENDCASE
      END;

    next:  PUBLIC PROCEDURE =
      BEGIN
        minusExp, validReal:  BOOLEAN ← FALSE;
        exp:  INTEGER ← 0;
        f1, f10:  REAL;

        SELECT char FROM
          IODefs.ControlZ => popIncludeFile[];
          '! => includeFile[];
          IODefs.TAB, IODefs.SP, IODefs.CR =>
                BEGIN
                  nextChar[TRUE];
                  next[]
                END;
          '{ => BEGIN
                  item ← leftC;
                  nextChar[TRUE]
                END;
          '; => BEGIN
                  item ← semi;
                  nextChar[TRUE]
                END;
          ': => BEGIN
                  item ← colon;
                  nextChar[TRUE]
                END;
          '[ => BEGIN
                  item ← leftB;
                  nextChar[TRUE]
                END;
          '] => BEGIN
                  item ← rightB;
                  nextChar[TRUE]
                END;
          ', => BEGIN
                  item ← comma;
                  nextChar[TRUE]
                END;
          '= => BEGIN
                  nextChar[FALSE];
                  IF char = '> THEN
                    BEGIN
                      item ← implies;
                      nextChar[TRUE]
                    END
                  ELSE item ← equal
                END;
          '← => BEGIN
                  item ← leftArrow;
                  nextChar[TRUE]
                END;
          '} => BEGIN
                  item ← rightC;
                  nextChar[TRUE]
                END;
          '/ => BEGIN
                  item ← slash;
                  nextChar[TRUE]
                END;
          '↑ => BEGIN
                  item ← upArrow;
                  nextChar[TRUE]
                END;
          '@ => BEGIN
                  item ← atSign;
                  nextChar[TRUE]
                END;
          '| => BEGIN
                  item ← vertical;
                  nextChar[TRUE]
                END;
          '& => BEGIN
                  item ← amperesand;
                  nextChar[TRUE]
                END;
          '+ => BEGIN
                  item ← plus;
                  nextChar[TRUE]
                END;
          '- => BEGIN
                  item ← minus;
                  nextChar[FALSE];
                  IF char = '- THEN
                    BEGIN
                      UNTIL char = IODefs.CR OR char = IODefs.ControlZ DO
                        nextChar[TRUE];
                        IF char = '- THEN
                          BEGIN
                            nextChar[FALSE];
                            IF char # '- THEN LOOP;
                            nextChar[TRUE];
                            EXIT
                          END
                      ENDLOOP;
                      next[]
                    END
                END;
          '* => BEGIN
                  item ← star;
                  nextChar[TRUE]
                END;
          '\ => BEGIN
                  item ← backSlash;
                  nextChar[TRUE]
                END;
          '> => BEGIN
                  nextChar[FALSE];
                  IF char = '= THEN
                    BEGIN
                      item ← greatEqual;
                      nextChar[TRUE]
                    END
                  ELSE item ← greater
                END;
          '< => BEGIN
                  nextChar[FALSE];
                  IF char = '= THEN
                    BEGIN
                      item ← lessEqual;
                      nextChar[TRUE]
                    END
                  ELSE item ← less
                END;
          '# => BEGIN
                  item ← pound;
                  nextChar[TRUE]
                END;
          '~ => BEGIN
                  item ← squiggle;
                  nextChar[TRUE]
                END;
          '( => BEGIN
                  item ← leftP;
                  nextChar[TRUE]
                END;
          ') => BEGIN
                  item ← rightP;
                  nextChar[TRUE]
                END;
          '' => BEGIN
                  item ← quote;
                  nextChar[TRUE]
                END;
          '" => BEGIN
                  item ← string;
                  chars.length ← 0;
                  DO
                    nextChar[FALSE];
                    IF char = IODefs.ControlZ THEN
                      BEGIN
                        error[213, FALSE];
                        EXIT
                      END;
                    IF char = '" THEN
                      BEGIN
                        nextChar[FALSE];
                        IF char # '" THEN EXIT
                      END;
                    chars[chars.length] ← char;
                    chars.length ← chars.length + 1
                  ENDLOOP;
                  newString ← makeLongString[chars.length];
                  FOR i:  CARDINAL IN [0..chars.length) DO
                    newString[i] ← chars[i]
                  ENDLOOP;
                  newString.length ← chars.length
                END;
          '? => BEGIN
                  CWF.SWF1[chars, "?%u", @genSymCtr];
                  genSymCtr ← genSymCtr + 1;
                  newString ← chars;
                  item ← name;
                  nextChar[TRUE]
                END;
          '$ => BEGIN
                  nextChar[FALSE];
                  chars.length ← 0;
                  UNTIL char = '$ DO
                    IF char = IODefs.ControlZ THEN
                      BEGIN
                        error[214, FALSE];
                        EXIT
                      END;
                    StringDefs.AppendChar[chars, char];
                    nextChar[FALSE]
                  ENDLOOP;
                  nextChar[TRUE];
                  newString ← chars;
                  item ← name
                END;
          IN ['A..'Z],
          IN ['a..'z] =>
                BEGIN
                  chars.length ← 0;
                  UNTIL char ~IN ['A..'Z] AND char ~IN ['a..'z]
                        AND char ~IN ['0..'9] DO
                    StringDefs.AppendChar[chars, char];
                    nextChar[FALSE]
                  ENDLOOP;
                  IF chars.length=3 THEN BEGIN
                    IF chars[0]='M OR chars[0]='m THEN BEGIN
                      IF chars[1]='A OR chars[1]='a THEN BEGIN                                              IF chars[2]='X OR chars[2]='x THEN BEGIN
                          item ← maximum; GOTO done;
                        END;
                      END ELSE IF chars[1]='I OR chars[1]='i THEN BEGIN
                        IF chars[2]='N OR chars[2]='n THEN BEGIN
                          item ← minimum; GOTO done;
                        END;
                      END;
                    END;
                  END;
                  newString ← chars;
                  item ← name
                EXITS
                  done => IF char=IODefs.SP OR char=IODefs.CR OR
                             char=IODefs.TAB THEN nextChar[TRUE];
                END;
          '.,
          IN ['0..'9] =>
                BEGIN
                  item ← number;
                  value ← 0.0;
                  UNTIL char ~IN ['0..'9] DO
                    validReal ← TRUE;
                    value ← value*10.0 + (char - '0);
                    nextChar[FALSE]
                  ENDLOOP;
                  IF char = '. THEN
                    BEGIN
                      nextChar[FALSE];
                      f10 ← 0.1;
                      UNTIL char ~IN ['0..'9] DO
                        validReal ← TRUE;
                        value ← value + f10*(char - '0);
                        f10 ← 0.1*f10;
                        nextChar[FALSE]
                      ENDLOOP
                    END;
                  IF char = 'e OR char = 'E THEN
                    BEGIN
                      nextChar[FALSE];
                      minusExp ← char = '-;
                      IF minusExp OR char = '+ THEN nextChar[FALSE];
                      IF char ~IN ['0..'9] THEN validReal ← FALSE
                      ELSE
                        UNTIL char ~IN ['0..'9] DO
                          exp ← exp*10 + (char - '0);
                          nextChar[FALSE]
                        ENDLOOP;
                      IF minusExp THEN exp ← -exp
                    END;
                  exp ← exp + scaleFactor[];
                  validReal ← validReal AND exp < 37 AND exp > -37;
                  IF validReal THEN
                    BEGIN
                      f1 ← 1.0E+1; f10 ← 1.0E+10;
                      IF exp < 0 THEN
                        BEGIN f1 ← 1.0/f1;f10 ← 1.0/f10; exp ← -exp END;
                      UNTIL exp < 10 DO
                        value ← value*f10;
                        exp ← exp - 10
                      ENDLOOP;
                      UNTIL exp = 0 DO
                        value ← value*f1;
                        exp ← exp - 1
                      ENDLOOP
                    END
                  ELSE error[102, FALSE]
                END
        ENDCASE =>
          BEGIN
            nextChar[TRUE];
            error[101, FALSE]
          END
      END;

    getSignedNumber:  PUBLIC PROCEDURE RETURNS[n:  REAL ← 1.0] =
      BEGIN
        negative:  BOOLEAN ← item = minus;

        IF negative THEN next[];
        IF item = number THEN
          BEGIN
            n ← IF negative THEN -value ELSE value;
            next[]
          END
        ELSE error[105, FALSE]
      END;

    LongEqualStrings:  PUBLIC PROCEDURE[s, S:  LONG STRING]
                                RETURNS[eq:  BOOLEAN ← FALSE] =
      BEGIN
        IF s.length = S.length THEN
          FOR i:  CARDINAL IN [0..s.length) DO
            eq ← s.text[i] = S[i];
            IF ~eq THEN EXIT
          ENDLOOP
      END;

    LongStringGetsString:  PUBLIC PROCEDURE[s, S:  LONG STRING] =
      BEGIN
        FOR i:  CARDINAL IN [0..S.length) DO
          s.text[i] ← S.text[i]
        ENDLOOP;
        s.length ← S.length
      END;

    searchKey:  PUBLIC PROCEDURE RETURNS[index:  keys] =
      BEGIN
        FOR i:  keys IN keys DO
          index ← i;
          IF newString.length # keyList[i].length THEN LOOP;
          FOR j:  CARDINAL IN [0..newString.length) DO
            IF keyList[i][j] # StringDefs.LowerCase[newString[j]] THEN EXIT;
          REPEAT
            FINISHED => RETURN;
          ENDLOOP
        ENDLOOP;
      END;

    GetLineAndCptr:  PUBLIC PROCEDURE RETURNS[STRING, CARDINAL] =
      BEGIN
        RETURN[line, cptr]
      END;

    line.length ← 0;
    char ← ' ;
  END.
4/19/83:- 
  original: [Cherry]<Barth>Thyme>1.97>spGlobalsimpl.mesa
  changes:
  1. next - modified to parse MAX and MIN. (Lower cases are also allowed.)
2/12/84:-
  original: [Cherry]<Thyme>System>CSIM02>spGlobalsimpl.mesa
  modified to support oldArgVector.