-- file CommanderImpl.mesa
--  edited by Johnsson,  9-Sep-80 20:35:49
--  edited by Sweet, 20-Apr-81 14:44:22
--  edited by Bruce, 10-Jan-81 15:32:29
--  edited by Satterthwaite, September 20, 1982 1:33 pm

DIRECTORY
  Ascii: TYPE USING [CR, DEL, ESC, NUL, SP],
  CommanderOps: TYPE USING [
    CommandBlock, CommandBlockHandle, CommandParam, ParamType],
  Exec: TYPE,
  Frame: TYPE USING [MyLocalFrame],
  Inline: TYPE USING [BITAND, BITOR],
  PrincOps: TYPE USING [StateVector],
  Runtime: TYPE USING [CallDebugger],
  Storage: TYPE USING [Node, String, CopyString, Free],
  String: TYPE USING [
    AppendChar, AppendString, EquivalentString, InvalidNumber,StringBoundsFault],
  Time: TYPE USING [AppendCurrent],
  TTY: TYPE,
  UserTerminal: TYPE;

CommanderImpl: PROGRAM
    IMPORTS Exec, Frame, Inline, Runtime, Storage, String, Time, TTY, UserTerminal
    EXPORTS CommanderOps = {
  OPEN String, CommanderOps, Ascii;
  
  CommandItem: TYPE = RECORD [
    cb: CommandBlockHandle, link: POINTER TO CommandItem];
  
  StringItem: TYPE = RECORD [link: POINTER TO StringItem, string: STRING];
  
  commandHead: POINTER TO CommandItem ← NIL;
  stringHead: POINTER TO StringItem ← NIL;
  
  SyntaxError: ERROR = CODE;
  Help: SIGNAL = CODE;
  BadName: ERROR = CODE;
  BadParam: ERROR [type: ParamType] = CODE;
  
  GetDebugger: PROC = {Runtime.CallDebugger[NIL]};
    
  ExtensionIs: PROC [name, ext: STRING] RETURNS [BOOL] = {
    t: STRING ← [40];
    i: CARDINAL;
    IF name.length <= ext.length THEN RETURN[FALSE];
    FOR i IN [name.length - ext.length..name.length) DO
      String.AppendChar[t, name[i]] ENDLOOP;
    RETURN [String.EquivalentString[t, ext]]};
    
  CheckForExtension: PROC [name, ext: STRING] = {
    i: CARDINAL;
    FOR i IN [0..name.length) DO IF name[i] = '. THEN RETURN ENDLOOP;
    String.AppendString[name, ext]};
    
  AddCommand: PUBLIC PROC [name: STRING, proc: PROC, numargs: CARDINAL]
      RETURNS [CommandBlockHandle] = {
    OPEN Storage;
    c: POINTER TO CommandItem ← Node[SIZE[CommandItem]];
    cb: CommandBlockHandle ← Node[
      SIZE[CommandBlock] + numargs*SIZE[CommandParam]];
    c↑ ← CommandItem[cb: cb, link: commandHead];
    commandHead ← c;
    cb.name ← name;
    cb.proc ← proc;
    cb.nparams ← numargs;
    RETURN [cb]};
    
  NewString: PROC [s: STRING] RETURNS [ns: STRING] = {
    OPEN Storage;
    si: POINTER TO StringItem ← Node[SIZE[StringItem]];
    si↑ ← StringItem[link: stringHead, string: ns ← CopyString[s]];
    stringHead ← si;
    RETURN};
    
  FreeStrings: PROC = {
    OPEN Storage;
    next: POINTER TO StringItem;
    WHILE stringHead # NIL DO
      next ← stringHead.link;
      Free[stringHead.string];
      Free[stringHead];
      stringHead ← next;
      ENDLOOP};
    
  WriteEOL: PROC = {IF ~TTY.NewLine[Exec.w] THEN TTY.PutCR[Exec.w]};
    
  firstCommand: BOOL ← TRUE;
  interactive: BOOL ← FALSE;
  
  SetupCom: PROC [c: POINTER TO Exec.CommandLine ← @Exec.commandLine] RETURNS [BOOL] =
    {RETURN[~(c.s = NIL OR c.i >= c.s.length)]};
    
  SkipToken: PROC [c: POINTER TO Exec.CommandLine ← @Exec.commandLine] = {
    foundToken: BOOL ← FALSE;
    ch: CHAR;
    DO
      IF c.i >= c.s.length THEN EXIT;
      ch ← c.s[c.i]; c.i ← c.i + 1;
      SELECT ch FROM
	Ascii.SP, Ascii.CR => IF foundToken THEN EXIT;
	ENDCASE => foundToken ← TRUE;
      ENDLOOP};
    
  -- code to get a line from the user, handling ESC and ?; stuffs it in line
  
  line: STRING ← NIL;
  lineTerminator: CHAR;
  Lindex: CARDINAL;
  
  AppendStringToLine: PROC [s: STRING] = {
    UNTIL (s.length + line.length) <= line.maxlength DO AddToLine[]; ENDLOOP;
    AppendString[line, s]};
    
  AppendCharToLine: PROC [c: CHAR] = {
    IF line.length = line.maxlength THEN AddToLine[];
    AppendChar[line, c]};
    
  ReadUserLine: PROC [newstring: BOOL] = {
    -- read line from user; also handles <ESC> and '? for input from user
    IF line = NIL THEN line ← Storage.String[80];
    [] ← TTY.GetEditedString[Exec.w, line, LineMonitor, newstring !
      resume => {newstring ← FALSE; RETRY}];
    Lindex ← 0};
    
  resume: SIGNAL = CODE;
  
  LineMonitor: PROC [c: CHAR] RETURNS [BOOL] = {
    SELECT c FROM
      CR => RETURN[TRUE];
      '? => {
	WriteChar['?];
	IF line.length = 0 THEN SIGNAL Help;
	PromptCompletions[];
	SIGNAL resume;
	ERROR};
      ESC => {ExtendLine[]; SIGNAL resume; ERROR};
      ENDCASE => RETURN [FALSE]};
    
  PromptCompletions: PROC = {
    id: STRING = [40];
    atLeastOne: BOOL ← FALSE;
    p: POINTER TO CommandItem;
    IF GetLastID[id] THEN
      FOR p ← commandHead, p.link UNTIL p = NIL DO
	IF PrefixString[prefix: id, of: p.cb.name] THEN {
	  IF ~atLeastOne THEN WriteEOL[];
	  WriteChar[SP];
	  WriteChar[SP];
	  WriteString[p.cb.name];
	  atLeastOne ← TRUE};
	ENDLOOP;
    IF atLeastOne THEN ReTypeLine[] ELSE UserTerminal.BlinkDisplay[]};
    
  ExtendLine: PROC = {
    i: CARDINAL;
    id: STRING = [40];
    match: STRING = [40];
    moreThanOne, atLeastOne: BOOL ← FALSE;
    p: POINTER TO CommandItem;
    IF GetLastID[id] THEN {
      FOR p ← commandHead, p.link UNTIL p = NIL DO
	IF PrefixString[prefix: id, of: p.cb.name] THEN
	  IF ~atLeastOne THEN {
	    AppendString[match, p.cb.name]; atLeastOne ← TRUE}
	  ELSE {AndString[match, p.cb.name]; moreThanOne ← TRUE};
	ENDLOOP};
    IF atLeastOne AND id.length # match.length THEN {
      FOR i IN [id.length..match.length) DO
	AppendCharToLine[match[i]]; WriteChar[match[i]]; ENDLOOP;
      IF moreThanOne THEN UserTerminal.BlinkDisplay[]}
    ELSE UserTerminal.BlinkDisplay[]};
    
  PrefixString: PROC [prefix, of: STRING] RETURNS [BOOL] = {
    IF prefix.length > of.length THEN RETURN[FALSE];
    FOR i: CARDINAL IN [0..prefix.length) DO
      IF ~EquivalentChar[prefix[i], of[i]] THEN RETURN[FALSE] ENDLOOP;
    RETURN [TRUE]};
    
  AndString: PROC [accum, s: STRING] = {
    FOR i: CARDINAL IN [0..s.length) DO
      IF ~EquivalentChar[accum[i], s[i]] THEN BEGIN accum.length ← i; RETURN END;
      ENDLOOP;
    accum.length ← s.length};
    
  GetLastID: PROC [id: STRING] RETURNS [BOOL] = {
    i, start: CARDINAL;
    c: CHAR;
    IF line.length = 0 THEN RETURN[FALSE];
    start ← line.length;
    FOR i DECREASING IN [0..line.length) DO
      IF AlphaNumeric[c ← line[i]] THEN start ← i
      ELSE IF c = '] OR c = SP THEN EXIT ELSE RETURN[FALSE];
      ENDLOOP;
    FOR i IN [start..line.length) DO id[i - start] ← line[i] ENDLOOP;
    id.length ← line.length - start;
    RETURN [id.length # 0]};
    
  AlphaNumeric: PROC [c: CHAR] RETURNS [BOOL] = {
    RETURN [Alphabetic[c] OR Digit[c]]};
    
  Alphabetic: PROC [c: CHAR] RETURNS [BOOL] = {
    RETURN [Inline.BITAND[c, 337b] IN [100b..132b]]};
    
  Digit: PROC [c: CHAR] RETURNS [BOOL] = {
    RETURN [c IN ['0..'9]]};
    
  EquivalentChar: PROC [c, d: CHAR] RETURNS [BOOL] = {
    RETURN [Inline.BITOR[c, 40b] = Inline.BITOR[d, 40b]]};
    
  AddToLine: PROC = INLINE {line ← Storage.CopyString[line, 80]};
    
  ReTypeLine: PROC = {WriteEOL[]; WriteString[line]};
    
  -- code to handle characters
  
  command: STRING = [100];
  executing: BOOL ← FALSE;
  Cindex: CARDINAL;
  currentChar: CHAR;
  
  EndOfString: SIGNAL = CODE;
  
  GetChar: PROC RETURNS [CHAR] ← GetCommandChar;
  
  PutBackChar: PROC ← PutBackCommandChar;
  
  GetCommandChar: PROC RETURNS [CHAR] = {
    IF Cindex >= command.length THEN currentChar ← NUL
    ELSE BEGIN currentChar ← command[Cindex]; Cindex ← Cindex + 1; END;
    RETURN [currentChar]};
    
  PutBackCommandChar: PROC = {
    IF currentChar = NUL THEN RETURN;
    IF Cindex = 0 THEN ERROR;
    Cindex ← Cindex - 1};
    
  CommandOverFlow: SIGNAL = CODE;
  
  SetUpCommand: PROC RETURNS [BOOL] = {
    BEGIN
    ENABLE StringBoundsFault => SIGNAL CommandOverFlow;
    RETURN [IF interactive THEN CopyFromLine[] ELSE CopyFromExecCommand[]];
    END};
    
  CopyFromLine: PROC RETURNS [BOOL] = {
    c: CHAR ← NUL;
    DO
      IF Lindex >= line.length THEN RETURN [FALSE];
      c ← line[Lindex];
      Lindex ← Lindex + 1;
      IF c # SP AND c # CR THEN EXIT;
      ENDLOOP;
    command.length ← 0;
    DO
      AppendChar[command, c];
      IF c = '] OR Lindex >= line.length THEN EXIT;
      c ← line[Lindex];
      Lindex ← Lindex + 1;
      ENDLOOP;
    Cindex ← 0;
    RETURN [TRUE]};
    
  SkipExecBlanks: PROC [c: POINTER TO Exec.CommandLine ← @Exec.commandLine]
      RETURNS [ch: CHAR] = {
    UNTIL c.i >= c.s.length DO
      ch ← c.s[c.i]; c.i ← c.i + 1; IF ch # SP AND ch # CR THEN EXIT;
      ENDLOOP};
    
  WriteChar: PROC [ch: CHAR] = {TTY.PutChar[Exec.w, ch]};
    
  WriteString: PROC [s: STRING] = {TTY.PutString[Exec.w, s]};
    
  WriteLine: PROC [s: STRING] = {TTY.PutLine[Exec.w, s]};
  
  EndOf: PROC [c: POINTER TO Exec.CommandLine ← @Exec.commandLine] RETURNS [BOOL] = {
    RETURN [c.s = NIL OR c.i >= c.s.length]};
    
  CopyFromExecCommand: PROC [c: POINTER TO Exec.CommandLine ← @Exec.commandLine]
      RETURNS [BOOL] = {
    ch: CHAR;
    IF ~SetupCom[c] THEN {interactive ← TRUE; RETURN [FALSE]};
    ch ← SkipExecBlanks[c];
    IF EndOf[c] THEN
      IF firstCommand THEN {interactive ← TRUE; RETURN [FALSE]}
      ELSE SIGNAL CommandExit;
    command.length ← 0;
    WriteEOL[];
    WriteChar['<];
    WriteChar['>];
    DO
      AppendChar[command, ch];
      WriteChar[ch];
      IF ch = '] OR EndOf[c] THEN EXIT;
      ch ← c.s[c.i]; c.i ← c.i + 1;
      ENDLOOP;
    WriteEOL[];
    Cindex ← 0;
    RETURN [TRUE]};
    
  GetName: PROC [n: STRING] = {
    n.length ← 0;
    DO
      IF AlphaNumeric[GetChar[]] THEN AppendChar[n, currentChar] ELSE EXIT;
      ENDLOOP;
    PutBackChar[];
    SkipBlanks[];
    IF GetChar[] # '[ THEN SE[]};
    
  SkipBlanks: PROC = {
    DO IF GetChar[] # SP THEN {PutBackChar[]; RETURN} ENDLOOP};
    
  -- code to parse user command
  
  
  ParseCommand: PROC [state: POINTER TO PrincOps.StateVector] = {
    proc: STRING = [40];
    cb: CommandBlockHandle;
    i: CARDINAL;
    GetName[proc];
    cb ← FindProc[proc].cb;
    FOR i IN [0..cb.nparams) DO
      state.stk[i] ← GetArg[cb, cb.params[i].type];
      IF GetChar[] # (IF i = cb.nparams - 1 THEN '] ELSE ',) THEN SE[];
      ENDLOOP;
    state.dest ← LOOPHOLE[cb.proc];
    state.stkptr ← cb.nparams};
    
  FindProc: PROC [name: STRING] RETURNS [p: POINTER TO CommandItem] = {
    FOR p ← commandHead, p.link UNTIL p = NIL DO
      IF EquivalentString[name, p.cb.name] THEN RETURN; ENDLOOP;
    ERROR BadName};
    
  GetArg: PROC [cb: CommandBlockHandle, t: ParamType] RETURNS [a: UNSPECIFIED] = {
    s: STRING = [100];
    SkipBlanks[];
    SELECT GetChar[] FROM
      '" => {
	IF t # string THEN ERROR BadParam[t];
	DO
	  IF GetChar[] = '" AND GetChar[] # '" THEN {PutBackChar[]; EXIT};
	  IF executing THEN AppendChar[s, currentChar];
	  ENDLOOP;
	IF executing THEN a ← NewString[s]};
      '' => {IF t # character THEN ERROR BadParam[t]; a ← GetChar[]};
      IN ['0..'9], '(, '- => {
	IF t # numeric THEN ERROR BadParam[t];
	PutBackChar[];
	a ← ExpressionToNumber[]};
      IN ['a..'z], IN ['A..'Z] => {
	SELECT t FROM
	  boolean =>
	    IF currentChar = 'T THEN a ← GetTRUE[t]
	    ELSE IF currentChar = 'F THEN a ← GetFALSE[t];
	  string => {
	    DO
	      SELECT currentChar FROM
	        ',, '], CR, NUL => {PutBackChar[]; EXIT};
	        ENDCASE => IF executing THEN AppendChar[s, currentChar];
	      [] ← GetChar[];
	      ENDLOOP;
	    IF executing THEN a ← NewString[s]};
	  ENDCASE => ERROR BadParam[t]};
      ENDCASE => ERROR BadParam[t];
    SkipBlanks[];
    RETURN};
    
  GetTRUE: PROC [t: ParamType] RETURNS [BOOL←TRUE] = {
    IF GetChar[] # 'R THEN ERROR BadParam[t];
    IF GetChar[] # 'U THEN ERROR BadParam[t];
    IF GetChar[] # 'E THEN ERROR BadParam[t]};
    
  GetFALSE: PROC [t: ParamType] RETURNS [BOOL←FALSE] = {
    IF GetChar[] # 'A THEN ERROR BadParam[t];
    IF GetChar[] # 'L THEN ERROR BadParam[t];
    IF GetChar[] # 'S THEN ERROR BadParam[t];
    IF GetChar[] # 'E THEN ERROR BadParam[t]};
    
  -- code to parse user commands in interactive mode
  
  
  ParsePromptedCommand: PROC = {
    proc: STRING = [40];
    cb: CommandBlockHandle;
    IF GetLastID[proc] THEN {
      cb ← FindProc[proc].cb; GetPromptedArgs[cb]; Confirm[]; RETURN};
    lineTerminator ← CR};
    
  CRFound: PROC [c: CHAR] RETURNS [BOOL] = {RETURN [c = CR]};
    
  GetPromptedArgs: PROC [cb: CommandBlockHandle] = {
    i: CARDINAL;
    cindex: CARDINAL;
    cstring: STRING = [100];
    
    GetArgChar: PROC RETURNS [c: CHAR] = {
      IF cindex >= cstring.length THEN currentChar ← NUL
      ELSE BEGIN currentChar ← cstring[cindex]; cindex ← cindex + 1; END;
      RETURN [currentChar]};
      
    PutBackArgChar: PROC = {
      IF currentChar = NUL THEN RETURN;
      IF cindex = 0 THEN ERROR;
      cindex ← cindex - 1};
      
    GetChar ← GetArgChar;
    PutBackChar ← PutBackArgChar;
    AppendCharToLine['[];
    FOR i IN [0..cb.nparams) DO
      WriteString["\n  "L];
      WriteString[cb.params[i].prompt];
      WriteChar[':];
      WriteChar[' ];
      [] ← TTY.GetEditedString[Exec.w, cstring, CRFound, TRUE];
      cindex ← 0;
      [] ← GetArg[cb, cb.params[i].type];
      AppendStringToLine[cstring];
      AppendCharToLine[',];
      ENDLOOP;
    IF cb.nparams # 0 THEN line[line.length - 1] ← '] ELSE AppendCharToLine[']];
    GetChar ← GetCommandChar;
    PutBackChar ← PutBackCommandChar};
    
  Confirm: PROC = {
    char: CHAR;
    WriteString[" [confirm]"L];
    DO
      char ← TTY.GetChar[Exec.w];
      SELECT char FROM
	DEL => SIGNAL TTY.Rubout;
	CR => {WriteEOL[]; EXIT};
	SP => {WriteString["\n  <>"L]; EXIT};
	ENDCASE => WriteChar['?];
      ENDLOOP;
    lineTerminator ← char};
    
  -- parsing arithmetic expressions
  
  symbol: Symbol;
  Symbol: TYPE = RECORD [
    body: SELECT tag: * FROM
      num => [val: INTEGER], delim => [char: CHAR], ENDCASE];
  Num: TYPE = num Symbol;
  
  SE: PROC = {ERROR SyntaxError};
    
  Scan: PROC = {
    v8, v10, radix, number: CARDINAL;
    digits: ARRAY CHAR ['0..'9] OF CARDINAL = [0, 1, 2, 3, 4, 5, 6, 7, 8, 9];
    firstchar: BOOL ← TRUE;
    v8 ← v10 ← 0;
    SkipBlanks[];
    DO
      SELECT GetChar[] FROM
	IN ['0..'9] => {
	  v8 ← v8*8 + digits[currentChar];
	  v10 ← v10*10 + digits[currentChar]};
	'M => {
	  IF ~firstchar THEN SE[];
	  IF ~(GetChar[] = 'O AND GetChar[] = 'D) THEN SE[];
	  IF ~Alphabetic[GetChar[]] THEN PutBackChar[] ELSE SE[];
	  symbol ← [delim['!]];
	  RETURN};
	'b, 'B => {number ← v8; radix ← 8; GOTO exponent};
	'd, 'D => {number ← v10; radix ← 10; GOTO exponent};
	SP => GOTO done;
	NUL => IF ~firstchar THEN GOTO done ELSE {symbol ← nul; RETURN};
	'(, '/, '*, '+, '-, '), '], ', =>
	  IF firstchar THEN {symbol ← [delim[currentChar]]; RETURN}
	  ELSE {PutBackChar[]; GOTO done};
	ENDCASE => SIGNAL InvalidNumber;
      firstchar ← FALSE;
      REPEAT
	done => {symbol ← [num[v10]]; RETURN};
	exponent => {
	  IF firstchar THEN SE[];
	  v10 ← 0;
	  WHILE Digit[GetChar[]] DO
	    v10 ← v10*10 + digits[currentChar];
	    REPEAT FINISHED => PutBackChar[]; -- took one too many
	    ENDLOOP;
	  THROUGH [1..v10] DO number ← number*radix ENDLOOP;
	  symbol ← [num[number]];
	  RETURN};
      ENDLOOP};
    
  nul: Symbol = [delim[NUL]];
  
  Primary: PROC RETURNS [n: Num] = {
    WITH s: symbol SELECT FROM
      delim => {
	IF s.char # '( THEN SE[];
	Scan[];
	n ← Exp[];
	WITH symbol SELECT FROM
	  delim => IF char = ') THEN {Scan[]; RETURN};
	  ENDCASE;
	SE[]};
      num => {n ← s; Scan[]; RETURN};
      ENDCASE};
    
  Factor: PROC RETURNS [n: Num] = {
    WITH symbol SELECT FROM
      delim =>
	IF char = '- THEN {Scan[]; n ← Primary[]; n.val ← -n.val; RETURN};
      ENDCASE;
    RETURN [Primary[]]};
    
  Product: PROC RETURNS [n: Num] = {
    x: Num;
    n ← Factor[];
    DO
      WITH symbol SELECT FROM
	delim =>
	  SELECT char FROM
	    '* => {Scan[]; n.val ← Factor[].val*n.val};
	    '/ => {Scan[]; x ← Factor[]; n.val ← n.val/x.val};
	    '! => {Scan[]; x ← Factor[]; n.val ← n.val MOD x.val};
	    ENDCASE => EXIT;
	ENDCASE => EXIT;
      ENDLOOP;
    RETURN};
    
  Exp: PROC RETURNS [n: Num] = {
    n ← Product[];
    DO
      WITH symbol SELECT FROM
	delim =>
	  SELECT char FROM
	    '+ => {Scan[]; n.val ← Product[].val + n.val};
	    '- => {Scan[]; n.val ← n.val - Product[].val};
	    '], ', => {PutBackChar[]; EXIT};
	    NUL, ') => EXIT;
	    ENDCASE => SE[];
	ENDCASE => EXIT;
      ENDLOOP;
    RETURN};
    
  ExpressionToNumber: PROC RETURNS [INTEGER] = {
    Scan[]; RETURN[Exp[].val]};
    
  ShowSE: PROC = {
    IF ~executing THEN {WriteChar['?]; RETURN};
    WriteEOL[];
    IF interactive THEN WriteString[command];
    WriteEOL[];
    THROUGH [1..(Cindex + (IF interactive THEN 0 ELSE 2))) DO
      WriteChar['.]; ENDLOOP;
    WriteChar['↑]};
    
  Driver: PROC = {
    state: --lst-- PrincOps.StateVector;
    newline: BOOL;
    ci: POINTER TO CommandItem;
    i: CARDINAL;
    BEGIN
    ENABLE {
      SyntaxError, InvalidNumber, StringBoundsFault => {
        ShowSE[]; GO TO abort};
      CommandOverFlow => {
        WriteEOL[]; WriteString["Command too long!"L]; GO TO abort};
      BadName => {ShowSE[]; WriteString[" not found!"L]; GO TO abort};
      BadParam => {
	ShowSE[];
	WriteString[" expected "L];
	SELECT type FROM
	  string => WriteString["string"L];
	  character => WriteString["character"L];
	  numeric => WriteString["numerical"L];
	  ENDCASE;
	WriteString[" parameter"L];
	GO TO abort};
      TTY.Rubout => {WriteString[" XXX"L]; GO TO abort};
      Help => {
	WriteEOL[];
	FOR ci ← commandHead, ci.link UNTIL ci = NIL DO
	  WriteString[ci.cb.name];
	  WriteChar['[];
	  FOR i IN [0..ci.cb.nparams) DO
	    IF i # 0 THEN WriteChar[',];
	    SELECT ci.cb.params[i].type FROM
	      string => WriteChar['"];
	      character => WriteChar[''];
	      ENDCASE;
	    WriteString[ci.cb.params[i].prompt];
	    SELECT ci.cb.params[i].type FROM string => WriteChar['"]; ENDCASE;
	    ENDLOOP;
	  WriteChar[']];
	  IF ci.link # NIL THEN BEGIN WriteChar[',]; WriteChar[' ]; END;
	  ENDLOOP;
	GO TO abort};
      UNWIND => FreeStrings[]};
    newline ← TRUE;
    executing ← FALSE;
    IF interactive THEN {
      WriteEOL[];
      WriteChar['<];
      WriteChar['>];
      DO
	ENABLE StringBoundsFault => {AddToLine[]; RESUME [line]};
	ReadUserLine[newline];
	newline ← FALSE;
	ParsePromptedCommand[];
	IF lineTerminator = CR THEN EXIT;
	ENDLOOP};
    GetChar ← GetCommandChar;
    PutBackChar ← PutBackCommandChar;
    executing ← TRUE;
    WHILE SetUpCommand[] DO
      ParseCommand[@state];
      state.instbyte ← 0;
      state.source ← LOOPHOLE[Frame.MyLocalFrame[]];
      firstCommand ← FALSE;
      TRANSFER WITH state;
      state ← STATE;
      ENDLOOP;
    executing ← FALSE;
    EXITS abort => NULL;
    END;
    FreeStrings[]};
    
  Quit: PROC = {SIGNAL CommandExit};
    
  WriteHerald: PROC = {
    time: STRING ← [22];
    WriteEOL[];
    IF h # NIL THEN WriteLine[h];
    Time.AppendCurrent[time];
    time.length ← time.length - 3;
    WriteLine[time]};
    
  h: STRING ← NIL;
  
  InitCommander: PUBLIC PROC [herald: STRING] = {
    h ← herald;
    [] ← AddCommand["Quit", Quit, 0];
    [] ← AddCommand["Debug", GetDebugger, 0]};
    
  CommandExit: SIGNAL = CODE;
    
  WaitCommands: PUBLIC PROC = {
    IF h = NIL THEN InitCommander[NIL];
    executing ← interactive ← FALSE;
    firstCommand ← TRUE;
    WriteHerald[];
    DO Driver[ ! CommandExit => EXIT]; ENDLOOP};
    
  
  }.


-- Here is the grammar for the command line

CommandLine ::= PromptedCommandList <CR> | NonPromptedCommandList ;
		NonPromptedCommandList <EOF>
PromptedCommandList ::= PromptedCommand | Command | CommandList <SP> Command
		  | CommandList <SP> PromptedCommand
NonPromptedCommandList ::= Command | CommandList <SP> Command
Command ::= ID [ ParamList ]
PromptedCommand ::= ID <CR> PromptedParamList
ParamList ::= Param | ParamList , Param
PromptedParamList ::= Param | PromptedParamList <CR> Param
Param ::= " STRING " | ' CHAR | Expression | <empty>
Expression ::= Product | Expression + Product | Expression - Product
Product ::= Factor | Product * Factor | Product / Factor | Product MOD Factor
Factor ::= - Primary | Primary
Primary ::= NUM | ( Expression )