Linker errors when running JS TH splices with undeclared deps
Summary
On !12479 (merged), I noticed a bug in the running of JS TH splices. The following example runs fine with a non-JS compiler but fails with a linker error when using the JS backend.
The issue seems to be that it is unaware of a dependency on a package bundled with GHC. Normally I think GHC would just load this package, but it seems that the JS linker errors out instead.
Steps to reproduce
{-# LANGUAGE TemplateHaskell #-}
module Repro where
import GHC.Exts.Heap
import Control.Monad.IO.Class
-- this is a TH splice
do
let b = asBox "foo"
liftIO $ print b
return []
Then with the boot compiler:
ghc Roro.hs
[1 of 1] Compiling Roro ( Roro.hs, Roro.o )
0x420035f9d0
With the GHC JS backend:
❯ _build/stage1/bin/javascript-unknown-ghcjs-ghc Roro.hs
[1 of 1] Compiling Roro ( Roro.hs, Roro.o ) [Source file changed]
<no location info>: error:
panic! (the 'impossible' happened)
GHC version 9.11.20240524:
getDeps: Couldn't find home-module:
GHC.Exts.Heap.Closures
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/GHC/Utils/Panic.hs:190:37 in ghc:GHC.Utils.Panic
pprPanic, called at compiler/GHC/StgToJS/Linker/Linker.hs:496:28 in ghc:GHC.StgToJS.Linker.Linker
CallStack (from HasCallStack):
panic, called at compiler/GHC/Utils/Error.hs:507:29 in ghc:GHC.Utils.Error
Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
The error goes away if I explicitly add a -package ghc-heap
argument to the call.
Expected behavior
They should behave the same either both giving a helpful error, or both succeeding
Environment
- GHC version used: The Glorious Glasgow Haskell Compilation System, version 9.11.20240524
Edited by Teo Camarasu