[Haskell-cafe] ANN: BNFC-meta-0.1.0

Jonas Almström Duregård jonas.duregard at chalmers.se
Wed Sep 22 11:47:49 EDT 2010


I'm pleased to announce BNFC-meta-0.1.0!

BNFC-meta can take a quasi-quoted LBNF grammar (as used by the BNF
Converter) representation of a language and generate (using Template
Haskell) a number of wonderful tools for dealing with this language,
including:

* Abstract syntax types
* Lexer
* LALR Parser
* Pretty-printer
* Quasi-quoter

Apart from the quasi-quoter, these are all features of the BNF Converter,
but grammars can now be embedded directly into Haskell modules.

Here's an example of a small subset of C:

\begin{code}
{-# LANGUAGE QuasiQuotes #-}
module MiniLanguage where
import Language.LBNF

-- 'Compile' is a Template Haskell function, 'cf' is a QuasiQuoter.
compile [$cf|
antiquote "[" ":" ":]" ;
Fun.      Prog     ::= Typ Ident "(" ")" "{" [Stm] "}" ;
SDecl.    Stm      ::= Typ Ident ";"  ;
SAss.     Stm      ::= Ident "=" Expr ";"  ;
SIncr.    Stm      ::= Ident "++" ";"  ;
SWhile.   Stm      ::= "while" "(" Expr ")" "{" [Stm] "}" ;

ELt.      Expr0     ::= Expr1 "<" Expr1 ;
EPlus.    Expr1     ::= Expr1 "+" Expr2 ;
ETimes.   Expr2     ::= Expr2 "*" Expr3 ;
EVar.     Expr3     ::= Ident ;
EInt.     Expr3     ::= Integer ;

[].       [Stm]    ::= ;
(:).      [Stm]    ::= Stm [Stm] ;

_.        Stm      ::= Stm ";" ;
_.  Expr      ::= Expr0 ;
_.  Expr0     ::= Expr1 ;
_.  Expr1     ::= Expr2 ;
_.  Expr2     ::= Expr3 ;
_.  Expr3     ::= "(" Expr ")" ;

TInt.     Typ  ::= "int" ;
comment "/*" "*/" ;
comment "//" ;
|]
\end{code}



And here is a module that uses it:

\begin{code}
{-# LANGUAGE QuasiQuotes #-}
import MiniLanguage
import Language.LBNF(pp) -- overloaded pretty-printing function
import Prelude hiding (exp)

power :: Ident -> Integer -> Prog
power var x = [$prog|
// This quoter accepts C-style comments
int myPower() {
 int tmp;
 tmp = 0;

 // Things in [: :] are anti-quoted Haskell expressions.
 [: repeatWhile (Ident "tmp") x mult :]
} |] where
  -- [X:haskell:] means the anti-quoted expression represents non-terminal
X,
  -- Used to resolve ambiguities (in this case between Ident/Expr/Integer).
  mult = [$stm| [:var:] = [Ident:var:] * [Ident:var:] ; |]

-- Repeats a statement n times. (at least if variable var is 0... )
repeatWhile var n statement = [$stm|
  while ([Ident:var:] < [:n:]) {
    [Stm:statement:]
    [:var:] ++ ;
  }|]

pr = power (Ident "n") 10
main = putStr $ pp pr
\end{code}


There are a few more examples in the source tarball. More documentation on
these features will be supplied eventually :)

Best regards,
Jonas
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100922/868430f3/attachment.html


More information about the Haskell-Cafe mailing list