Template Haskell question
Simon Peyton-Jones
simonpj@microsoft.com
Mon, 30 Jun 2003 09:13:52 +0100
Yes, sorry, as Ian says, type splices just aren't implemented at the
moment. The error message is uninformative. =20
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
|=20
| Can anyone tell me what's wrong with this?
|=20
| -- ghc -fglasgow-exts -c TH.hs
| module TH where
| {
| import Language.Haskell.THSyntax;
|=20
| class HasZero a where
| {
| zero :: a;
| };
|=20
| aninstance :: TypQ -> Q [Dec];
| aninstance t =3D [d|
|=20
| instance HasZero $t where -- error here
| {
| zero =3D 0;
| };
|=20
| |];
|=20
| $(aninstance [t|Int|])
| $(aninstance [t|Integer|])
| }
|=20
|=20
| $ ghc -fglasgow-exts -c TH.hs
| TH.hs:14: Malformed context in instance header
|=20
| All I want to do is spin off a number instances for a number of
types...
|=20
| --
| Ashley Yakeley, Seattle WA
|=20
| _______________________________________________
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe