Here one of my favourite bugs in larger projects (IIRC, this
has partly been reported by me in the "Importing, hiding, and
exporting" thread):

-- A.hs -------------------------------------------------
module A where
data Foo = Foo -- Typo! Forgot "deriving Show"
-- B.hs -------------------------------------------------
module B where
import A
data Bar = Bar Foo deriving Show
data Baz = Baz Int deriving Show
-- Main.hs ----------------------------------------------
import A
import B
main :: IO ()
main = print (Bar Foo, Baz 42)
---------------------------------------------------------

   panne@jeanluc:~ > ghc -Wall -O -c A.hs
   ghc: module version changed to 1; reason: no old .hi file
   panne@jeanluc:~ > ghc -Wall -O -c B.hs
   ghc: module version changed to 1; reason: no old .hi file

[??? Why does B compile? And why is Baz's Show instance not in B.hi? ]

   panne@jeanluc:~ > ghc -Wall -O -c Main.hs

   Main.hs:4:
       No instance for `Show Baz' arising from use of `print' at Main.hs:4

   Main.hs:4:
       No instance for `Show Bar' arising from use of `print' at Main.hs:4

This one drove me mad several times, looking at the completely
wrong place (i.e. B.hs).    %-{

Cheers,
   Sven
-- 
Sven Panne                                        Tel.: +49/89/2178-2235
LMU, Institut fuer Informatik                     FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen              Oettingenstr. 67
mailto:[EMAIL PROTECTED]            D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne

Reply via email to