[Template-haskell] A subtle bug with GHC

Simon Peyton-Jones simonpj@microsoft.com
Thu, 6 Feb 2003 12:12:54 -0000


I believe I have fixed this problem. The current HEAD has the fix.

Thanks for reporting it -- sorry for slow service!

Simon

| -----Original Message-----
| From: Sean Seefried [mailto:seefried@itee.uq.edu.au]
| Sent: 20 January 2003 05:28
| To: template-haskell@haskell.org
| Subject: [Template-haskell] A subtle bug with GHC
|=20
| I've noticed a subtle bug with TH.  It took me some time to realise
what
| was happening.  First I will present my source files.
|=20
| --- [Splices.hs] ----
| module Splices where
|=20
| import Char
| import Language.Haskell.THSyntax
|=20
| debug f =3D [| do { putStrLn (show ( $(f) + 3)) ;
|                          putStrLn "Hello World!" } |]
|=20
| ----------------------------
| --- [ Main.hs] ---------
|=20
| module Main where
|=20
| import Language.Haskell.THSyntax
| import Splices
|=20
| main =3D $(debug [| (1::Integer) |])
| -----------------------------
|=20
| When I compile this from scratch using the command line:
|=20
| prompt>   ghc --make -fglasgow-exts -package haskell-src -package
| haskell98 Main.hs -o test
|=20
| we get
|=20
| prompt>
| Chasing modules from: Main.hs
| Compiling Splices          ( Splices.hs, ./Splices.o )
| Compiling Main             ( Main.hs, ./Main.o )
| Loading package base ... linking ... done.
| Loading package haskell98 ... linking ... done.
| Loading package haskell-src ... linking ... done.
| Linking ...
|=20
| And the program works as expected.  But I noticed that when I made a
| small change to Main.hs and recompiled the following would occur:
|=20
| Skipping  Splices          ( Splices.hs, ./Splices.o )
| Compiling Main             ( Main.hs, ./Main.o )
| Loading package base ... linking ... done.
| Loading package haskell98 ... linking ... done.
| Loading package haskell-src ... linking ... done.
|=20
| No instance for (Monad IO)
|   arising from a do statement at <compiler-generated-code>
| In a right-hand side of function `main':
|     $[splice](debug [| (1 :: Integer) |])
| In the definition of `main':
|     main =3D $[splice](debug [| (1 :: Integer) |])
| make: *** [all] Error 1
|=20
|=20
| I can repeat this error at will.  As long as Splices.hi and Splices.o
| are in existence the above error will occur when trying to recompile
| Main.hs.
|=20
| I was using ghc-5.05.20030118
|=20
| Sean Seefried
|=20
| _______________________________________________
| template-haskell mailing list
| template-haskell@haskell.org
| http://www.haskell.org/mailman/listinfo/template-haskell