-- September 6, 1982 12:26 am
-- ParseWindowImpl.mesa
-- Last Edited by: Gnelson, March 20, 1983 5:11 pm

DIRECTORY Atom, ParseWindow, ParseTable, ViewerClasses, Rope, TiogaOps, Parser, Lexer, IO, Unparser;

ParseWindowImpl: MONITOR 
  IMPORTS Atom, PT: ParseTable, Rope, TiogaOps, Parser, Lexer, Unparser, IO
  EXPORTS ParseWindow
= BEGIN OPEN ParseWindow;

ROPE: TYPE = Rope.ROPE;

NewHandle: PUBLIC PROC [v: ViewerClasses.Viewer]
 					 RETURNS [h: Handle] = 
  { h ← NEW[HandleRep]
  ;  h.ph ← Parser.NewHandle[]
  ;  h.ph.in ← Lexer.NewHandle[]
  ;  h.viewer ← v
  ;  h.content ← NIL
  ;  h.contentValid ← FALSE};

AddOp: PUBLIC PROC
         [h: Handle, 
          op: Rope.ROPE, 
          alias: ROPE,
          bp: INTEGER,  
          f: OperatorType, 
          c: Rope.ROPE,
          u: INT ← 0] =
    {p: PT.Properties ← NEW[PT.PRec ← [name: Atom.MakeAtom[op]]];
     IF alias # NIL THEN p.alias ← Atom.MakeAtom[alias];
     p.bindingPower ← bp;
     p.closer ← IF c = NIL THEN NIL ELSE h.ph.table.Search[Atom.MakeAtom[c], NIL];
     p.unparserType ← u;
     SELECT f FROM
       infix => p.infix ← TRUE;
       subfixMatchfix => p.subfix ← p.matchfix ← TRUE;
       matchfix => p.matchfix ← TRUE;
       prefix => p.prefix ← TRUE;
       infixPrefix => p.infix ← p.prefix ← TRUE;
       closefix => p.closefix ← TRUE
     ENDCASE => ERROR;
     h.ph.table.Enter[p];
     IF Rope.Length[alias] = 2 AND h.ph.in.type[Rope.Fetch[alias, 0]] = op
     THEN h.ph.in.AddOpPair[alias.Fetch[0], alias.Fetch[1]];
     IF Rope.Length[op] = 2 AND h.ph.in.type[Rope.Fetch[op, 0]] = op
     THEN h.ph.in.AddOpPair[op.Fetch[0], op.Fetch[1]]};

TiogaNode: TYPE = TiogaOps.Ref;

NodeProc: TYPE = PROC [n: TiogaNode, pw: Handle] 
                     RETURNS [keepgoing: BOOL];

NodeMap: PROC [ p: NodeProc, pw: Handle] RETURNS [didAllNodes: BOOL] =
  {  --! should lock the selection & the document
     root: TiogaNode ← TiogaOps.ViewerDoc[pw.viewer];
     RETURN[NM2[p, TiogaOps.FirstChild[root], pw]]} ;

NM2: PROC [p: NodeProc, n: TiogaNode, pw: Handle] 
       RETURNS [didAllNodes: BOOL] 
= {RETURN [n = NIL OR 
               (p[n, pw] AND NM2[p, TiogaOps.FirstChild[n], pw] 
                          AND NM2[p, TiogaOps.Next[n], pw])]};
                          
ParseViewer: PUBLIC PROC [pw: Handle] =
 {newContent: LIST OF NodeContent ← NIL;
  n: TiogaNode ← TiogaOps.ViewerDoc[pw.viewer];
  Foo: SAFE PROC[root: TiogaOps.Ref] = TRUSTED
    {success: BOOL;
     tree: REF;
     text: ROPE;
     pw.contentValid ← TRUE;
     WHILE n # NIL DO
       IF TiogaOps.FirstChild[n] = NIL 
       THEN {[success, tree, text] ←  PN2[n, pw];
       		  IF success THEN newContent ← CONS[[text, tree], newContent]};
       n ← TiogaOps.StepForward[n];
    ENDLOOP};
 TiogaOps.CallWithLocks[Foo, n];
 pw.content ← newContent};
  
PN2: PROC [n: TiogaNode, pw: Handle] 
 RETURNS [success: BOOL, tree: REF ANY, text: ROPE]
 =
  {r: Rope.ROPE;
   vc: VerdictAndCulprit;
   errorMessage: ROPE ← NIL;
   text ← TiogaOps.GetRope[n];
   -- next three lines try to skip parsing if old parsed result is present in pw.contents:
   { l: LIST OF NodeContent ← pw.content
   ; WHILE l # NIL AND l.first.text # text DO l ← l.rest ENDLOOP
   ; IF l # NIL THEN { success ← TRUE ; tree ← l.first.tree ; text ← l.first.text ; RETURN } };
   IF ~ pw.contentValid THEN RETURN;
   pw.ph.in.in ← IO.RIS[Rope.Cat[text, " "]];
   pw.ph.in.eof ← FALSE;
   pw.ph.in.error ← NIL;
   pw.ph.in.Lex[];
   IF pw.ph.in.eof THEN {success ← TRUE; tree ← text ← NIL; RETURN}; 
   pw.ph.Parse[];
   pw.ph.result ← tree ← CONS[pw.ph.result, NIL]; 
     -- necessary because WellFormed and Unparse work on the CAR of their argument
     -- and ignore the cdr.
   IF pw.ph.error = NIL AND pw.ph.eof 
     THEN {vc ← pw.WellFormed[pw.ph.result];
              IF vc.verdict # Yes
              THEN errorMessage ← "Not a WFF"
              ELSE {vc.culprit ← NIL; errorMessage ← NIL}}
     ELSE {vc.culprit ← NIL; 
             errorMessage ← IF pw.ph.error # NIL THEN pw.ph.error ELSE "Bad Syntax"};
   
   r ← Unparser.Unparse[pw.ph.result, vc.culprit, 60, pw.ph.table, pw.ph.openCount]; 
     --! change "60" to "width of window"
   tree ← NARROW[pw.ph.result, LIST OF REF ANY].first;
   IF pw.ph.error # NIL OR ~pw.ph.eof 
   THEN {r ← Rope.Cat[r, " \000", Rope.FromRefText[pw.ph.in.buf], "\000"];
            WHILE ~ IO.EndOf[pw.ph.in.in]
              DO r ← Rope.Cat[r, Rope.FromChar[IO.GetChar[pw.ph.in.in]]]
              ENDLOOP};
   {i, j: INT; 
    i ← r.SkipTo[0, "\000"];
    TiogaOps.SelectNodes[viewer: pw.viewer, start: n, end: n, pendingDelete: TRUE, level:char];
    IF i = r.Length[] 
    THEN TiogaOps.InsertRope[r]
    ELSE {j ← r.SkipTo[i + 1, "\000"];
            TiogaOps.InsertRope[Rope.Cat[r.Substr[0, i], r.Substr[i+1, j - i - 1], r.Substr[j+1]]];
            TiogaOps.SetSelection
              [pw.viewer, [n,  i], [n, j - 1]]}};
  success ← (errorMessage = NIL);
  text ← TiogaOps.GetRope[n]};

AddTree: PUBLIC PROC[pw: Handle, tree: REF]
= {text: ROPE ← Unparser.Unparse[LIST[tree], NIL, 60, pw.ph.table, 0];
    n: INT ← Rope.Index[text, 0, Rope.FromChar[10C]];
    m: INT ← Rope.Index[text, 0, Rope.FromChar[')]];
    p: INT ← SELECT TRUE FROM n < m + 1 => n ENDCASE => m + 1;
    header: ROPE ← Rope.Substr[text, 0, p];
    nd:  TiogaNode ← TiogaOps.LastWithin[TiogaOps.ViewerDoc[pw.viewer]];
    Foo: SAFE PROC[root: TiogaOps.Ref] =  CHECKED
      {TiogaOps.SelectNodes[pw.viewer, nd, nd, node, FALSE];
       TiogaOps.Break[];
       TiogaOps.UnNest[];
       TiogaOps.InsertRope[header];
       TiogaOps.Break[];
       TiogaOps.Nest[];
       TiogaOps.InsertRope[text]};
    TiogaOps.CallWithLocks[Foo, TiogaOps.ViewerDoc[pw.viewer]];
    pw.content ← CONS[[text, tree], pw.content]};
    

HasForm: PUBLIC PROC[f: REF ANY, 
                   op: ATOM, 
                   Arg1: SyntacticPredicate, 
                   Arg2: SyntacticPredicate ← NIL]  
      RETURNS [VerdictAndCulprit] =
  {WITH Car[NARROW[f]] SELECT FROM
    g: LIST OF REF ANY =>
      {IF Car[g] # op THEN RETURN [[OfCourseNot, g]];
       IF (Arg2 = NIL) # (Cddr[g] = NIL)
       THEN RETURN[[OfCourseNot, f]];
       {aw: VerdictAndCulprit ← Arg1[Cdr[g]];
        IF aw.verdict # Yes THEN RETURN [[No, aw.culprit]];
        IF Cddr[g] = NIL THEN RETURN [[Yes, NIL]];
        aw ← Arg2[Cddr[g]];
        IF aw.verdict # Yes THEN RETURN [[No, aw.culprit]];
        RETURN [[Yes, NIL]]}}
     ENDCASE => RETURN [[OfCourseNot, f]]};
 
Or: PUBLIC PROC [aw1, aw2: VerdictAndCulprit] 
    RETURNS [r: VerdictAndCulprit] =
  {SELECT TRUE FROM
     aw1.verdict = Yes OR aw2.verdict = Yes => r ← [Yes, NIL];
     aw1.verdict = No => r ← aw1;
     aw2.verdict = No => r ← aw2;
     aw1.verdict = OfCourseNot AND aw2.verdict = OfCourseNot  
     => r ← aw1
    ENDCASE => ERROR};
    
Se: TYPE = REF ANY;
    
Car: PROC [r: Se] RETURNS [Se] = {RETURN[NARROW[r, LIST OF REF ANY].first]};

Cdr: PROC [r: Se] RETURNS [Se] = {RETURN[NARROW[r, LIST OF REF ANY].rest]};

Cadr: PROC [r: Se] RETURNS [Se] = {RETURN[Car[Cdr[r]]]};

Caddr: PROC [r: Se] RETURNS [Se] = {RETURN[Car[Cdr[Cdr[r]]]]};

Cddr: PROC [r: Se] RETURNS [Se] = {RETURN[Cdr[Cdr[r]]]};

Caar: PROC [r: Se] RETURNS [Se] = {RETURN[Car[Car[r]]]};

Cadar: PROC [l: Se] RETURNS [Se] =
{ RETURN[ Car[ Cdr[ Car[ l ] ] ] ] };

Caddar: PROC [l: Se] RETURNS [Se] =
{ RETURN[ Car[ Cdr[ Cdr[ Car[ l ] ] ] ] ]   };

Cadddar: PROC [l: Se] RETURNS [Se] =
{ RETURN[ Car[ Cdr[ Cdr[ Cdr[ Car[ l ] ] ] ] ] ]  };

Cadddr: PROC [l: Se] RETURNS [Se] =
{ RETURN[ Car[ Cdr[ Cdr[ Cdr[ l ] ] ] ] ]  };

Caddddar: PROC [l: Se] RETURNS [Se] =
{ RETURN[ Car[ Cdr[ Cdr[ Cdr[ Cdr[ Car[ l ] ] ] ] ] ] ]   };

Cddar: PROC [l: Se] RETURNS [Se] =
{ RETURN[ Cdr[ Cdr[ Car[ l ] ] ] ]  };


END.