MODULE Grammars; IMPORT AGRS, Names, Library, Parser, Texts; CONST SetBits= MAX(SET)+1; MaxStrLength*= 30; TYPE ParserProc= PROCEDURE; ParserTerm= POINTER TO RECORD(AGRS.TermDesc) handler: ParserProc; END; BuilderTerm= POINTER TO RECORD(AGRS.TermDesc) property: AGRS.Name; END; GenericBuilderTerm= POINTER TO RECORD(AGRS.TermDesc) END; SetLimitTerm= POINTER TO RECORD(AGRS.TermDesc) limit: LONGINT; END; ReaderProc= PROCEDURE(VAR in: CHAR); VAR Read*: ReaderProc; BackSpace*: PROCEDURE; input: Texts.Reader; inputString: Names.CharPtr; inputText: Texts.Text; position,limit: LONGINT; EmptyMarker: AGRS.Atomic; spaceChars,idChars: Library.CharSet; i: INTEGER; temp: AGRS.SubTerm; tempDis: AGRS.Disjunction; disjunctionBuilder,continuationBuilder: AGRS.SystemTerm; fieldBuilder,blockBuilder: AGRS.SystemTerm; nameToTreeBuilder: AGRS.SystemTerm; localConsName,classConsName: AGRS.Name; grammarName*,followName: AGRS.Name; treeName*,propertyName*,valueName*,rootName*: AGRS.Name; sentenceName*,genericRootName,emptyName: AGRS.Name; spaceCharsName,idCharsName: AGRS.Name; genericAttrName*,disjunctionName*,continuationName*: AGRS.Name; fieldName*,blockName*: AGRS.Name; optionName*: AGRS.Name; terminalName*,attrName*,constructName*,parseEndName: AGRS.Name; parseName*,defaultGrammarName: AGRS.Name; charParser*,stringParser*: AGRS.Name; charTerminalParser*,stringTerminalParser*: AGRS.Name; spaceParser,nameParser*,idParser*,recurrenceParser: AGRS.Name; PROCEDURE ReadFile(VAR ch: CHAR); BEGIN REPEAT Texts.Read(input, ch); INC(position); UNTIL input.elem=NIL; END ReadFile; PROCEDURE ReadString(VAR ch: CHAR); BEGIN ch:= inputString[position]; INC(position); END ReadString; PROCEDURE BackSpaceFile; BEGIN DEC(position); Texts.OpenReader(input,inputText,position); END BackSpaceFile; PROCEDURE BackSpaceString; BEGIN DEC(position); END BackSpaceString; PROCEDURE SkipSpaces; VAR ch: CHAR; spaces: AGRS.Term; BEGIN spaces:= spaceCharsName.Value(); WITH spaces: Library.CharSet DO REPEAT Read(ch); UNTIL ~(ORD(ch) MOD SetBits IN spaces.value[ORD(ch) DIV SetBits]) OR (position>limit); BackSpace; END; END SkipSpaces; PROCEDURE pSkipSpaces; BEGIN SkipSpaces; AGRS.Continue; END pSkipSpaces; PROCEDURE ParseConstruct; VAR expect,skeleton: AGRS.Term; newTerm: AGRS.Tree; BEGIN expect:= treeName.indirection; skeleton:= rootName.indirection; IF expect=AGRS.Variable THEN NEW(newTerm); WITH skeleton: AGRS.Tree DO newTerm^:= skeleton^; ELSE newTerm.Init(skeleton.indirection); END; treeName.Assign(newTerm); AGRS.Continue; treeName.Restore; ELSIF AGRS.Equal(expect,skeleton) THEN AGRS.Continue; ELSE AGRS.Fail; END; END ParseConstruct; PROCEDURE ParseGenericSkeleton(builder: AGRS.Term; check: BOOLEAN); VAR skeleton: AGRS.Class; BEGIN IF check & (treeName.indirection#AGRS.Variable) THEN AGRS.Fail; RETURN END; AGRS.Push(builder); AGRS.Push(treeName); NEW(skeleton); skeleton.Init(genericRootName); treeName.Assign(skeleton); grammarName.Reduce; treeName.Restore; END ParseGenericSkeleton; PROCEDURE ParseDisjunctConstruct; BEGIN ParseGenericSkeleton(disjunctionBuilder,TRUE); END ParseDisjunctConstruct; PROCEDURE ParseContinueConstruct; BEGIN ParseGenericSkeleton(continuationBuilder,TRUE); END ParseContinueConstruct; PROCEDURE ParseFieldConstruct; BEGIN ParseGenericSkeleton(fieldBuilder,TRUE); END ParseFieldConstruct; PROCEDURE ParseBlockConstruct; BEGIN Names.LocalBlock; ParseGenericSkeleton(blockBuilder,TRUE); Names.EndBlock; END ParseBlockConstruct; PROCEDURE ParseGenericAttribute; VAR builder: GenericBuilderTerm; BEGIN NEW(builder); builder.Init(treeName.indirection); ParseGenericSkeleton(builder,FALSE); END ParseGenericAttribute; PROCEDURE LocalConstruct; VAR newTerm: AGRS.Block; BEGIN IF treeName.indirection IS AGRS.Tree THEN NEW(newTerm); newTerm.Init(treeName.indirection.indirection); treeName.Assign(newTerm); AGRS.Continue; treeName.Restore(); ELSE AGRS.Fail; END; END LocalConstruct; PROCEDURE ClassConstruct; VAR newTerm: AGRS.Class; BEGIN IF treeName.indirection IS AGRS.Tree THEN NEW(newTerm); newTerm.Init(treeName.indirection.indirection); treeName.Assign(newTerm); AGRS.Continue; treeName.Restore(); ELSE AGRS.Fail; END; END ClassConstruct; PROCEDURE ParseAttribute; VAR prop,val: AGRS.Term; root: AGRS.Name; builder: BuilderTerm; BEGIN prop:= propertyName.indirection; IF ~(prop IS AGRS.Name) THEN prop:= prop.indirection; END; WITH prop: AGRS.Name DO root:= treeName.indirection.indirection(AGRS.Name); root.Assign(AGRS.Variable); prop.Assign(EmptyMarker); val:= treeName.Evaluate(prop); prop.Restore; root.Restore; IF val=EmptyMarker THEN val:= AGRS.Variable; END; NEW(builder); builder.Init(treeName.indirection); builder.property:= prop; AGRS.Push(builder); treeName.Assign(val); grammarName.Reduce; treeName.Restore; END; END ParseAttribute; PROCEDURE ParseTerminal; VAR val: AGRS.Term; builder: BuilderTerm; BEGIN NEW(builder); builder.Init(treeName.indirection); builder.property:= NIL; AGRS.Push(builder); grammarName.Reduce; END ParseTerminal; PROCEDURE ParseCharTerminal; VAR chRead: CHAR; chTerm: AGRS.Term; BEGIN Read(chRead); chTerm:= grammarName.Value(); IF chRead=chTerm(Library.Character).value THEN AGRS.Continue; ELSE AGRS.Fail; END; END ParseCharTerminal; PROCEDURE ParseChar; VAR chRead: CHAR; chTerm: Library.Character; BEGIN Read(chRead); chTerm:= Library.NewChar(chRead); AGRS.Unify(treeName,chTerm); END ParseChar; PROCEDURE ParseTheStringPrim(termExpect: AGRS.Term); VAR strExpect: Names.CharPtr; chRead: CHAR; i: INTEGER; BEGIN IF ~(termExpect IS Library.String) THEN AGRS.Fail; RETURN END; strExpect:= termExpect(Library.String).value; i:= 0; WHILE (ilimit); BackSpace; END; t.handler; position:= oldPos; IF inputString=NIL THEN Texts.OpenReader(input,inputText,oldPos); END; END Reduce; PROCEDURE pParse; VAR txt,r: AGRS.Term; BEGIN txt:= sentenceName.Value(); WITH txt: Library.Text DO inputText:= txt.base; inputString:= NIL; position:= txt.startOffset; Texts.OpenReader(input,txt.base,txt.startOffset); limit:= txt.endOffset; Read:= ReadFile; BackSpace:= BackSpaceFile; ELSE WITH txt: Library.String DO position:= 0; inputString:= txt.value; limit:= txt.Length(); Read:= ReadString; BackSpace:= BackSpaceString; END; END; treeName.Assign(AGRS.Variable); r:= grammarName.Evaluate(parseEndName); treeName.Restore; IF r.indirection#AGRS.failName THEN IF ~AGRS.Continued() THEN AGRS.result:= r.indirection; END; RETURN END; r:= Library.NewError(Library.SyntaxError); r.Reduce; END pParse; PROCEDURE ExtractTree; VAR newTerm: AGRS.Term; BEGIN SkipSpaces; IF position