[Template-haskell] A subtle bug with GHC

Sean Seefried seefried@itee.uq.edu.au
Mon, 20 Jan 2003 15:28:26 +1000


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.

--- [Splices.hs] ----
module Splices where

import Char
import Language.Haskell.THSyntax

debug f = [| do { putStrLn (show ( $(f) + 3)) ;
                         putStrLn "Hello World!" } |]

----------------------------
--- [ Main.hs] ---------

module Main where

import Language.Haskell.THSyntax
import Splices

main = $(debug [| (1::Integer) |])
-----------------------------

When I compile this from scratch using the command line:

prompt>   ghc --make -fglasgow-exts -package haskell-src -package 
haskell98 Main.hs -o test

we get

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 ...

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:

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.

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 = $[splice](debug [| (1 :: Integer) |])
make: *** [all] Error 1


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.

I was using ghc-5.05.20030118

Sean Seefried