{-# LANGUAGE QuasiQuotes #-} import JavaletteLight import Language.LBNF(pp) -- overloaded pretty-printing function import Prelude hiding (exp) {- This Javalette Light program is parsed at compile time, and replaced by it's abstract syntax representation. The 'holes' in square brackets are anti-quoted Haskell expression. The QuasiQuoter prog is generated from the grammar in JavaletteLight.hs (it corresponds to the category Prog). -} prg x v e = [$prog| int f() { int a; [:SWhile (EInt 10 :: Exp) []:] int a; int [:v:]; int tmp; while (n < [Exp:e:]) { n = n + 1; tmp = a + b; a = b; b = tmp; } } |] st v = [$stm| [:v:] = 1; |] pr = prg (st (Ident "n")) (Ident "n") [$exp|n|] main = putStr $ pp pr