In ghci, Template Haskell getDoc triggers obscure error "attempting to use module .. not loaded" for unrelated module when reloading
with the following simple example, A.hs
module A where
irrelevant :: IO ()
irrelevant = putStrLn "irrelevant"
B.hs
{-# LANGUAGE TemplateHaskell #-}
module B (test) where
import Language.Haskell.TH
test :: IO ()
test = do
let s = $(getDoc (DeclDoc ''Double) >>= \doc -> [|doc|])
-- let s = $(isExtEnabled EmptyCase >>= \doc -> [|doc|])
print s
and loaded them in ghci session (which mocks a cabal repl session), first it loads them well, and once I changed B.hs and reload with :r
, then it shows the following exception, which is obscure as happened in irrelevant code, and does not seem to be correct. :r
again reloads the modules well.
$ ghci A B
GHCi, version 9.6.1: https://www.haskell.org/ghc/ :? for help
[1 of 2] Compiling A ( A.hs, interpreted )
[2 of 2] Compiling B ( B.hs, interpreted )
Ok, two modules loaded.
-- change B.hs (add a space)
ghci> :r
[2 of 2] Compiling B ( src/B.hs, interpreted ) [Source file changed]
src/B.hs:9:11: error: [GHC-87897]
• Exception when trying to run compile-time code:
<interactive>:1:1: error:
attempting to use module `main:A' (src/A.hs) which is not loaded
Code: (getDoc (DeclDoc ''Double)
>>=
\ doc
-> [| doc |]
pending(rn) [<doc, Language.Haskell.TH.Syntax.lift doc>])
• In the untyped splice:
$(getDoc (DeclDoc ''Double) >>= \ doc -> [| doc |])
|
9 | let s = $(getDoc (DeclDoc ''Double) >>= \doc -> [|doc|])
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Failed, one module loaded.
Other TH actions do not trigger this behavior. tested with GHC 9.6
Edited by Ian-Woo Kim