Generics in 6.8.0 RC
Dirk Kleeblatt
klee at cs.tu-berlin.de
Sat Sep 22 04:45:50 EDT 2007
Dear *,
I just failed to get generic classes working with snapshot
ghc-6.8.0.20070920-i386-unknown-linux.tar.bz2. Are generics broken in
the RC, or am I doing something wrong?
I tried the following module:
---
module Gen where
import Data.Generics
class Equal a where
equal :: a -> a -> Bool
equal {| Unit |} Unit Unit = True
equal {| u :+: v |} (Inl x) (Inl y) = equal x y
equal {| u :+: v |} (Inr x) (Inr y) = equal x y
equal {| u :+: v |} _ _ = False
equal {| u :*: v |} (x1 :*: x2) (y1 :*: y2) = equal x1 y1 && equal
x2 y2
instance Equal Bool
---
and got
---
klee at romulus:~/tmp> ghci -fglasgow-exts -XGenerics
GHCi, version 6.8.0.20070920: http://www.haskell.org/ghc/ :? for help
Loading package base ... linking ... done.
Prelude> :l Gen.hs
[1 of 1] Compiling Gen ( Gen.hs, interpreted )
Gen.hs:13:0:
Can't find interface-file declaration for variable GHC.Base.$gfromBool
Probable cause: bug in .hi-boot file, or inconsistent .hi file
Use -ddump-if-trace to get an idea of which file caused the error
In the first argument of `a', namely `(GHC.Base.$gfromBool b)'
In the first argument of `(\ a -> a)', namely
`(a (GHC.Base.$gfromBool b))'
In the expression: (\ a -> a) (a (GHC.Base.$gfromBool b))
Failed, modules loaded: none.
---
Using -ddump-if-trace as suggested gave me no idea of anything, ;-) but
if you're interested, I can post the dump, too.
Any hints appreciated!
Kind regards,
Dirk
More information about the Glasgow-haskell-users
mailing list