panic in allocateRegsAndSpill when using FMA primops
Summary
I get the following error when compiling some code containing FMA primops.
$ ghc -mfma -O2 TwoProdFMA.hs
[1 of 1] Compiling TwoProdFMA ( TwoProdFMA.hs, TwoProdFMA.o ) [Flags changed]
<no location info>: error:
panic! (the 'impossible' happened)
GHC version 9.9.20231105:
allocateRegsAndSpill: Cannot read from uninitialized register
%vDouble_nCE
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/GHC/Utils/Panic.hs:186:37 in ghc-9.9-inplace:GHC.Utils.Panic
pprPanic, called at compiler/GHC/CmmToAsm/Reg/Linear.hs:837:20 in ghc-9.9-inplace:GHC.CmmToAsm.Reg.Linear
CallStack (from HasCallStack):
panic, called at compiler/GHC/Utils/Error.hs:511:29 in ghc-9.9-inplace:GHC.Utils.Error
Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
Steps to reproduce
Compile the following program with -mfma -O2
:
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
module TwoProdFMA where
import GHC.Exts
twoProductFloat# :: Float# -> Float# -> (# Float#, Float# #)
twoProductFloat# x y = let !r = x `timesFloat#` y
in (# r, fmsubFloat# x y r #)
Expected behavior
The program should compile fine.
Environment
- GHC version used: 9.8.1, master (e451139f)
- Operating System: Linux (also confirmed on Windows with 9.8.1)
- System Architecture: x86_64 (does not reproduce on AArch64 macOS)