[Haskell-cafe] Automatic derivation (TemplateHaskell?)
Joel Reymont
joelr1 at gmail.com
Thu Apr 5 10:19:15 EDT 2007
Here's a complete working example. There seems to be an error in the
parser but everything is derived fine.
*Main> run fooParser "Foo(10)"
Foo (Int 10)
*Main> run fooParser "Foo(10.5)"
parse error at (line 1, column 7):
unexpected "."
expecting digit or ")"
FunParser.hs:
Replace "show seen" with "show (seen + 1)" in args'
baz.hs:
import Text.ParserCombinators.Parsec hiding ( parse )
import qualified Text.ParserCombinators.Parsec as P
import qualified Text.ParserCombinators.Parsec.Token as T
import Text.ParserCombinators.Parsec.Language( emptyDef )
import Data.Derive.TH
import FunParser
data NumExpr
= Int Integer
| Num Double
deriving Show
instance FunParser NumExpr where
parse = numExpr
instance FunParser Integer where
parse = T.integer lexer
instance FunParser Int where
parse = T.integer lexer >>= return . fromInteger
data Foo
= Foo NumExpr
| Bar Int NumExpr
deriving Show
lexer = T.makeTokenParser emptyDef
identifier = T.identifier lexer
reserved = T.reserved lexer
integer = T.integer lexer
float = T.float lexer
numExpr :: GenParser Char a NumExpr
numExpr =
choice [ integer >>= return . Int
, float >>= return . Num
]
$( derive makeFunParser ''Foo )
fooParser :: GenParser Char a Foo
fooParser = parse
run p input =
case (P.parse p "" input) of
Left err -> putStr "parse error at " >> print err
Right x -> print x
More information about the Haskell-Cafe
mailing list