[Template-haskell] example of derive using Template Haskell?
S. Alexander Jacobson
alex at alexjacobson.com
Mon Jan 10 21:45:20 EST 2005
Does [d|...] work in 6.2.2 and if so, how do I
enable it?
This code gives a syntax error:
{-# OPTIONS -fglasgow-exts #-}
module Tth where
import Language.Haskell.THSyntax
import Language.Haskell.Syntax
fooFunc = [d|funD "foo" [clause [] (normalB $ litE $ StringL "bar") [] ] |]
goo = [|2|]
---
{-# OPTIONS -fglasgow-exts #-}
import Tth
foo = $(goo)
$(fooFunc)
If I eliminate the d in "[d|" I get an error about
Dec conflicting with Exp.
I can actually use template Haskell in 6.2.2, can
anyone provide an example of deriving a class?
-Alex-
______________________________________________________________
S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com
More information about the template-haskell
mailing list