
Yes, sorry, as Ian says, type splices just aren't implemented at the moment. The error message is uninformative. This is useful info though -- someone wants type splices! Simon | -----Original Message----- | From: haskell-cafe-admin@haskell.org [mailto:haskell-cafe-admin@haskell.org] On Behalf Of Ashley | Yakeley | Sent: 27 June 2003 23:57 | To: haskell-cafe@haskell.org | Subject: Template Haskell question | | Can anyone tell me what's wrong with this? | | -- ghc -fglasgow-exts -c TH.hs | module TH where | { | import Language.Haskell.THSyntax; | | class HasZero a where | { | zero :: a; | }; | | aninstance :: TypQ -> Q [Dec]; | aninstance t = [d| | | instance HasZero $t where -- error here | { | zero = 0; | }; | | |]; | | $(aninstance [t|Int|]) | $(aninstance [t|Integer|]) | } | | | $ ghc -fglasgow-exts -c TH.hs | TH.hs:14: Malformed context in instance header | | All I want to do is spin off a number instances for a number of types... | | -- | Ashley Yakeley, Seattle WA | | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe