Template Haskell question

Ashley Yakeley ashley@semantic.org
Fri, 27 Jun 2003 15:57:19 -0700


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