[Haskell-cafe] Mutual recursive modules with GHC: Classes, instances

Henning Thielemann lemming at henning-thielemann.de
Wed May 4 05:10:25 EDT 2005


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'


More information about the Haskell-Cafe mailing list