[Haskell-cafe] Mutual recursive modules with GHC: Classes,
instances
Simon Peyton-Jones
simonpj at microsoft.com
Wed May 4 05:26:47 EDT 2005
hi-boot files can't contain class declarations. This should be checked,
but isn't, hence puzzling message.
GHC 6.4 has a better setup. Actually, it still doesn't check for
absence of class decls, but it will shortly.
Simon
| -----Original Message-----
| From: haskell-cafe-bounces at haskell.org
[mailto:haskell-cafe-bounces at haskell.org] On Behalf Of
| Henning Thielemann
| Sent: 04 May 2005 10:10
| To: Haskell Cafe
| Subject: [Haskell-cafe] Mutual recursive modules with GHC: Classes,
instances
|
|
| I tried to set up mutual recursive modules according to section
4.6.10. of
| the manual of GHC-6.2.2. I illustrate my problems with a simple
fictitious
| example.
|
| ---- A.hi-boot ----
|
| module A where
|
|
| class GHC.Num.Num a => C a where
| answer :: a
|
| f :: B.T -> GHC.Num.Int
|
|
| ---- A.hs ----
|
| module A where
|
| import B
|
| class Num a => C a where
| answer :: a
|
| instance C Int where
| answer = 42
|
| f :: B.T -> Int
| f (B.Cons x) = x
|
|
| ---- B.hs ----
|
| module B where
|
| import {-# SOURCE #-} A
|
|
| data T = Cons Int
|
| newAnswer :: Int
| newAnswer = A.answer + 1
|
| --------------
|
|
| $ ghc --make A.hs B.hs
| Chasing modules from: A.hs,B.hs
| Compiling B ( B.hs, B.o )
|
| B.hs:1:
| Failed to find interface decl for `A.$dmanswer'
| from module `A'
| _______________________________________________
| Haskell-Cafe mailing list
| Haskell-Cafe at haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list