I'm pleased to announce BNFC-meta-0.1.0!
<div><br></div><div>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:</div>


<div><br></div><div>* Abstract syntax types</div><div>* Lexer </div><div>* LALR Parser</div><div>* Pretty-printer</div><div>* Quasi-quoter</div><div><br></div><div>Apart from the quasi-quoter, these are all features of the BNF Converter, but grammars can now be embedded directly into Haskell modules. <br>

<br>Here&#39;s an example of a small subset of C:<br><br>\begin{code}<br><font face="verdana, sans-serif"><font face="&#39;courier new&#39;, monospace">{-# LANGUAGE QuasiQuotes #-}<br>
module MiniLanguage where<br>import Language.LBNF<br><br>-- &#39;Compile&#39; is a Template Haskell function, &#39;cf&#39; is a QuasiQuoter.<br>compile [$cf|<br>antiquote &quot;[&quot; &quot;:&quot; &quot;:]&quot; ;<br>Fun.      Prog     ::= Typ Ident &quot;(&quot; &quot;)&quot; &quot;{&quot; [Stm] &quot;}&quot; ;<br>

SDecl.    Stm      ::= Typ Ident &quot;;&quot;  ;<br>SAss.     Stm      ::= Ident &quot;=&quot; Expr &quot;;&quot;  ;<br>SIncr.    Stm      ::= Ident &quot;++&quot; &quot;;&quot;  ;<br>SWhile.   Stm      ::= &quot;while&quot; &quot;(&quot; Expr &quot;)&quot; &quot;{&quot; [Stm] &quot;}&quot; ;<br>

<br>ELt.      Expr0     ::= Expr1 &quot;&lt;&quot; Expr1 ;<br>EPlus.    Expr1     ::= Expr1 &quot;+&quot; Expr2 ;<br>ETimes.   Expr2     ::= Expr2 &quot;*&quot; Expr3 ;<br>EVar.     Expr3     ::= Ident ;<br>EInt.     Expr3     ::= Integer ;<br>

<br>[].       [Stm]    ::= ;<br>(:).      [Stm]    ::= Stm [Stm] ;<br><br>_.        Stm      ::= Stm &quot;;&quot; ;<br>_.  Expr      ::= Expr0 ;<br>_.  Expr0     ::= Expr1 ;<br>_.  Expr1     ::= Expr2 ;<br>_.  Expr2     ::= Expr3 ;<br>

_.  Expr3     ::= &quot;(&quot; Expr &quot;)&quot; ;<br><br>TInt.     Typ  ::= &quot;int&quot; ;<br>comment &quot;/*&quot; &quot;*/&quot; ;<br>comment &quot;//&quot; ;</font><br>|]</font><br><div>\end{code}<br><br><br><br>

And here is a module that uses it:<br><br>\begin{code}</div><div><font face="&#39;courier new&#39;, monospace">{-# LANGUAGE QuasiQuotes #-}</font></div><div><font face="&#39;courier new&#39;, monospace">import MiniLanguage</font></div>

<div><font face="&#39;courier new&#39;, monospace">import Language.LBNF(pp) -- overloaded pretty-printing function</font></div><div><font face="&#39;courier new&#39;, monospace">import Prelude hiding (exp)</font></div>
<div><font face="&#39;courier new&#39;, monospace"><br></font></div><div><font face="&#39;courier new&#39;, monospace">power :: Ident -&gt; Integer -&gt; Prog</font></div>
<div><font face="&#39;courier new&#39;, monospace">power var x = [$prog|</font></div><div><font face="&#39;courier new&#39;, monospace">// This quoter accepts C-style comments </font></div>
<div><font face="&#39;courier new&#39;, monospace">int myPower() {</font></div><div><font face="&#39;courier new&#39;, monospace"> int tmp;</font></div><div><font face="&#39;courier new&#39;, monospace"> tmp = 0;</font></div>

<div><font face="&#39;courier new&#39;, monospace"><br></font></div><div><font face="&#39;courier new&#39;, monospace"> // Things in [: :] are anti-quoted Haskell expressions.</font></div>
<div><font face="&#39;courier new&#39;, monospace"> [: repeatWhile (Ident &quot;tmp&quot;) x mult :]</font></div><div><font face="&#39;courier new&#39;, monospace">} |] where </font></div>
<div><font face="&#39;courier new&#39;, monospace">  -- [X:haskell:] means the anti-quoted expression represents non-terminal X,</font></div><div><font face="&#39;courier new&#39;, monospace">  -- Used to resolve ambiguities (in this case between Ident/Expr/Integer).</font></div>

<div><font face="&#39;courier new&#39;, monospace">  mult = [$stm| [:var:] = [Ident:var:] * [Ident:var:] ; |]</font></div><div><font face="&#39;courier new&#39;, monospace"><br>
</font></div><div><font face="&#39;courier new&#39;, monospace">-- Repeats a statement n times. (at least if variable var is 0... )</font></div><div><font face="&#39;courier new&#39;, monospace">repeatWhile var n statement = [$stm|</font></div>

<div><font face="&#39;courier new&#39;, monospace">  while ([Ident:var:] &lt; [:n:]) {</font></div><div><font face="&#39;courier new&#39;, monospace">    [Stm:statement:]</font></div>
<div><font face="&#39;courier new&#39;, monospace">    [:var:] ++ ;</font></div><div><font face="&#39;courier new&#39;, monospace">  }|]</font></div><div><font face="&#39;courier new&#39;, monospace"><br>
</font></div><div><font face="&#39;courier new&#39;, monospace">pr = power (Ident &quot;n&quot;) 10</font></div><div><font face="&#39;courier new&#39;, monospace">main = putStr $ pp pr</font></div>
</div><div>\end{code}</div><div><div><br></div><div><br>There are a few more examples in the source tarball. More documentation on these features will be supplied eventually :)<br><br></div>Best regards,</div><div>Jonas</div>