{-# LANGUAGE QuasiQuotes #-} module JavaletteLight where import Language.LBNF {- compile is a TH function and cf is a QuasiQuoter for LBNF. compile will generate most of the code that BNFC, Happy and Alex would (and some new stuff) and splice it directly into this module. -} compile [$cf| -- This is a new pragma. The rest of the grammar is original JL. antiquote "[" ":" ":]" ; -- Javalette Light: a simple subset of C, covering -- programs with a single zero-argument function. -- example: koe.jll -- ordinary rules Fun. Prog ::= Typ Ident "(" ")" "{" [Stm] "}" ; SDecl. Stm ::= Typ Ident ";" ; SAss. Stm ::= Ident "=" Exp ";" ; SIncr. Stm ::= Ident "++" ";" ; SWhile. Stm ::= "while" "(" Exp ")" "{" [Stm] "}" ; ELt. Exp0 ::= Exp1 "<" Exp1 ; EPlus. Exp1 ::= Exp1 "+" Exp2 ; ETimes. Exp2 ::= Exp2 "*" Exp3 ; EVar. Exp3 ::= Ident ; EInt. Exp3 ::= Integer ; EDouble. Exp3 ::= Double ; []. [Stm] ::= ; (:). [Stm] ::= Stm [Stm] ; -- coercions _. Stm ::= Stm ";" ; _. Exp ::= Exp0 ; _. Exp0 ::= Exp1 ; _. Exp1 ::= Exp2 ; _. Exp2 ::= Exp3 ; _. Exp3 ::= "(" Exp ")" ; TInt. Typ ::= "int" ; TDouble. Typ ::= "double" ; -- pragmas comment "/*" "*/" ; comment "//" ; entrypoints Prog, Stm, Exp ; |]