[Oberon] syntax constrained editor: is Active Oberon LL1 ?

Patrick.Hunziker at unibas.ch Patrick.Hunziker at unibas.ch
Sun Mar 13 19:54:19 CET 2005


I have had a look at building a syntax-constrained editor using the Oberon
grammar and COCO.
In principle, making the permitted text entries available at each caret position
is straightforward because they are anyway used for the parse tree at the same
location by COCO.
I have encountered some unexpected hindrances, however:
- Coco is slightly out of sync with the distributions it is found in.
(CRA.Mod: "IF ch = r.eot" does not work, naturally).
- I had problems finding an Oberon EBNF grammar which is LL1. I thought the
language is, in principle. However, the grammar at
http://www.oberon.ethz.ch/EBNF.html  (*Oberon-1 ?*)
is not, neither is
the one in the distribution,
neither is the one for Active Oberon at
http://bluebottle.ethz.ch/languagereport/node7.html
(I have not tried the Oberon-2 one at
http://statlab.uni-heidelberg.de/projects/oberon/kurs/www/Oberon2.EBNF.html
and the one at
http://www.elegosoft.com/cgi-bin/cvsweb.cgi/m3/pm3/language/parsing/m3coco/test/misc/oberon.atg?rev=1.1.1.1&content-type=text/x-cvsweb-markup&cvsroot=PM3)

In all these Cases Coco complained that there are LL1 inconsistencies in the
grammar, what could easily be confirmed visually.
This might be a problem of reformulation, or a fundamental problem ??
How do the compiler builders at ETH see this problem ?
Below the example of the ActiveOberonGrammar.ATG and the Coco complaints.
Greetings
Pat

COMPILER ActiveOberon 	(* A grammar for Active Oberon *)

IMPORT Strings;
VAR alternatives:ARRAY 1024 OF CHAR;

CHARACTERS
  eol      = CHR(13) .
  letter   = "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz" .
  digit    = "0123456789" .
  hexDigit = digit + "ABCDEF" .
  noQuote  = ANY - '"' - eol  .

IGNORE  CHR(9) + CHR(10) + CHR(11) + CHR(12) + CHR(13)

COMMENTS
  FROM "(*" TO "*)" NESTED

TOKENS
  ident   =  letter { letter | digit } .
  integer  =  digit { digit } | digit { hexDigit } "H" .
  real  =  digit { digit } "." { digit }
           [ ("E" | "D") [ "+" | "-" ] digit { digit } ] .
  CharConstant = digit { hexDigit } "X" .
  string  =  '"' { noQuote } '"' .

PRODUCTIONS
ActiveOberon           =  Module .
Module 	= 	"MODULE" ident ";" [ImportList] {Definition} {DeclSeq} Body ident
".".
ImportList 	= 	"IMPORT" ident [":=" ident] {"," ident [":=" ident ]} ";".
Definition 	= 	"DEFINITION" ident ["REFINES" Qualident] {"PROCEDURE" ident
[FormalPars] ";"} "END" ident.
DeclSeq 	= 	"CONST" {ConstDecl ";"} | "TYPE" {TypeDecl ";"} | "VAR" {VarDecl
";"} | {ProcDecl ";"}.
ConstDecl 	= 	IdentDef "=" ConstExpr.
TypeDecl 	= 	IdentDef "=" Type.
VarDecl 	= 	IdentList ":" Type.
ProcDecl 	= 	"PROCEDURE" ProcHead ";" {DeclSeq} Body ident.
ProcHead 	= 	[SysFlag] ["*" | "&"] IdentDef [FormalPars].
SysFlag 	= 	"[" ident "]".
FormalPars 	= 	"(" [FPSection {";" FPSection}] ")" [":" Qualident].
FPSection 	= 	["VAR"] ident {"," ident} ":" Type.
Type 	= 	Qualident
  	| 	"ARRAY" [SysFlag] [ConstExpr {"," ConstExpr}] "OF" Type
  	| 	"RECORD" [SysFlag] ["(" Qualident ")"] [FieldList] "END"
  	| 	"POINTER" [SysFlag] "TO" Type
  	| 	"OBJECT" [[SysFlag] ["(" Qualident ")"] ["IMPLEMENTS" Qualident] {DeclSeq}
Body]
  	| 	"PROCEDURE" [SysFlag] [FormalPars].
FieldDecl 	= 	[IdentList ":" Type].
FieldList 	= 	FieldDecl {";" FieldDecl}.
Body 	= 	StatBlock | "END".
StatBlock 	= 	"BEGIN" ["{"IdentList"}"] [StatSeq] "END".
StatSeq 	= 	Statement {";" Statement}.
Statement 	= 	[Designator ":=" Expr
  	| 	Designator ["(" ExprList")"]
  	| 	"IF" Expr "THEN" StatSeq {"ELSIF" Expr "THEN" StatSeq}["ELSE" StatSeq]
"END"
  	| 	"CASE" Expr "THEN" Case {"|" Case} ["ELSE" StatSeq] "END"
  	| 	"WHILE" Expr "DO" StatSeq "END"
  	| 	"REPEAT" StatSeq "UNTIL" Expr
  	| 	"FOR" ident ":=" Expr "TO" Expr ["BY" ConstExpr] "DO" StatSeq "END"
  	| 	"LOOP" StatSeq "END"
  	| 	"WITH" Qualident ":" Qualident "DO" StatSeq "END"
  	| 	"EXIT"
  	| 	"RETURN" [Expr]
  	| 	"AWAIT" "(" Expr ")"
  	| 	StatBlock
  	  	].
Case 	= 	[CaseLabels { "," CaseLabels } ":" StatSeq].
CaseLabels 	= 	ConstExpr [".." ConstExpr].
ConstExpr 	= 	Expr.
Expr 	= 	SimpleExpr [Relation SimpleExpr].
SimpleExpr 	= 	Term {MulOp Term}.
Term 	= 	["+"|"-"] Factor {AddOp Factor}.
Factor 	= 	Designator["(" ExprList")"] | number | CharConstant | string
  	| 	"NIL" | Set | "(" Expr ")" | "~" Factor.
Set 	= 	"{" [Element {"," Element}] "}".
Element 	= 	Expr [".." Expr].
Relation 	= 	"=" | "#" | "<" | "<=" | ">" | ">=" | "IN" | "IS".
MulOp 	= 	"*" | "DIV" | "MOD" | "/" | "&" .
AddOp 	= 	"+" | "-" | "OR" .
Designator 	= 	Qualident { "." ident | "["ExprList"]" | "" | "(" Qualident ")"
}.
ExprList 	= 	Expr {"," Expr}.
IdentList 	= 	IdentDef {"," IdentDef}.
Qualident 	= 	[ident "."] ident.
IdentDef 	= 	ident ["*"|"-"].
number	=	real | integer .
END ActiveOberon.

-------------------
Coco.Compile *
Coco/R - Compiler-Compiler V2.2
 checking
  Case deletable
  Statement deletable
  StatSeq deletable
  FieldDecl deletable
  FieldList deletable
  DeclSeq deletable
  LL1 error in Designator: "(" is  start & successor of deletable structure
  LL1 error in Statement: ident is  start of several alternatives.
  LL1 error in StatBlock: "END" is  start & successor of deletable structure
  LL1 error in Type: "END" is  start & successor of deletable structure
  LL1 error in Type: "END" is  start & successor of deletable structure
  LL1 error in Type: "END" is  start & successor of deletable structure
  LL1 error in Type: "BEGIN" is  start & successor of deletable structure
  LL1 error in ProcDecl: "END" is  start & successor of deletable structure
  LL1 error in ProcDecl: "BEGIN" is  start & successor of deletable structure
  LL1 error in Qualident: ident is  start & successor of deletable structure
  LL1 error in DeclSeq: "CONST" is  start of several alternatives.
  LL1 error in DeclSeq: "TYPE" is  start of several alternatives.
  LL1 error in DeclSeq: "VAR" is  start of several alternatives.
  LL1 error in DeclSeq: "PROCEDURE" is  start & successor of deletable structure
  LL1 error in Module: "END" is  start & successor of deletable structure
  LL1 error in Module: "BEGIN" is  start & successor of deletable structure
 +parser +scanner done




----------------------------------------------------------------
This message was sent using IMP, the Internet Messaging Program.




More information about the Oberon mailing list