[Hs-Generics] EMGM: deriving instances
Antoine Latter
aslatter at gmail.com
Wed Feb 18 21:39:25 EST 2009
Hello,
This is listed as the mailing list for EMGM on its website:
http://www.cs.uu.nl/wiki/GenericProgramming/EMGM
I'm not sure if I'm using the template Haskell deriving properly for
EMGM instances - I doesn't work for me for:
+ Data declarations which contain type synonyms
+ Data declarations which contain a Bool
I get errors like:
>>>>>
Exception when trying to run compile-time code:
Error! Unsupported constant type: Bool
Code: EMGM.derive 'A
<<<<<
I get a similar error if my data type uses a 'String' instead of a
Bool, but the error for the String goes away if I use [Char] instead.
Is this expected behavior? If I'm just running into the limits of
what EMGM template-Haskell deriving can do, that's okay. I just
didn't see these limitations described anywhere.
Thanks,
Antoine
---
I'm using GHC 6.10, with emgm-0.2 from hackage.
Here's the sample program I'm working with:
>>>>>
{-# LANGUAGE TemplateHaskell
, MultiParamTypeClasses
, FlexibleContexts
, FlexibleInstances
, OverlappingInstances
, UndecidableInstances
#-}
import qualified Generics.EMGM as EMGM
data MyData a = MkMyData
{ name :: [Char]
-- , flag :: Bool
-- , otherName :: String
, fa :: A a
, fb :: B a
}
data A a = MkA Int Bool a
data B a = MkB Char a
$(EMGM.derive ''MyData)
$(EMGM.derive ''A)
$(EMGM.derive ''B)
<<<<<
More information about the Generics
mailing list