Tag inference failure with -fprefer-byte-code
Compiling the following three modules fails the tag inference check (and causes a segfault in a larger application).
It seems to be an interaction between fat interface files and tag inference. Reverting d6ea8356 fixes the bug.
A.hs
module A where
data A = MkA { getA :: !(Maybe Bool) }
B.hs
{-# OPTIONS_GHC -fwrite-if-simplified-core #-}
module B where
import A
theA :: A
theA = MkA (Just True)
C.hs
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fwrite-if-simplified-core -fbyte-code-and-object-code -fprefer-byte-code #-}
module C where
import A
import B
$(case getA theA of { MkB x -> pure [] })
ghci.script
:load A.hs B.hs
import A
import B
let !x = getA theA
To reproduce either build C.hs
rm *.hi *.o
_build/stage1/bin/ghc -dtag-inference-checks -fforce-recomp C
[1 of 3] Compiling A ( A.hs, A.o )
[2 of 3] Compiling B ( B.hs, B.o, interpreted )
[3 of 3] Compiling C ( C.hs, C.o, interpreted )
ghc: internal error: Tag inference failed on:TagCheck failed on entry in A - value:ds1_sH8 _sH8::P64
Or execute ghci.script in ghci after having built B.hs first:
andi@horzube:~/ghc_infer_bytecode/tmp$ ../_debug/stage1/bin/ghc -dtag-inference-checks -fforce-recomp B -ddump-to-file -ddump-stg-final
[1 of 2] Compiling A ( A.hs, A.o )
[2 of 2] Compiling B ( B.hs, B.o )
andi@horzube:~/ghc_infer_bytecode/tmp$ ../_debug/stage1/bin/ghc -dtag-inference-checks --interactive < ghci.script
GHCi, version 9.7.20230130: https://www.haskell.org/ghc/ :? for help
ghci> Ok, two modules loaded.
ghci> ghci> ghci> ghci> ghci> <interactive>: internal error: Tag inference failed on:TagCheck failed on entry in A - value:ds1_sAP _sAP::P64
(GHC version 9.7.20230130 for x86_64_unknown_linux)
Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
Aborted (core dumped)
Edited by Andreas Klebinger