-O1 changes result at runtime, duplicating __DEFAULT case
Here is a program, which works as expected in GHC 8.4.1-alpha3 with -O0
, but changes it behaviour with -O1
.
{-# LANGUAGE MagicHash #-}
import qualified Data.Vector.Unboxed as U
import GHC.Exts
vec :: U.Vector Moebius
vec = U.singleton Moebius0
main :: IO ()
main = print $ U.head vec == U.head vec
data Moebius = Moebius0 | Moebius1 | Moebius2
deriving (Eq)
fromMoebius :: Moebius -> Int
fromMoebius Moebius0 = 0
fromMoebius Moebius1 = 1
fromMoebius Moebius2 = 2
toMoebius :: Int -> Moebius
toMoebius (I# i#) = tagToEnum# i#
{- ...unboxed vector instances, see file attached... -}
It is expected that this program will print True
. However, when compiled with -O1
it prints False
.
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 8.4.0.20180204
$ ghc -O0 Sieve.hs && ./Sieve
[1 of 1] Compiling Main ( Sieve.hs, Sieve.o ) [Optimisation flags changed]
Linking Sieve ...
True
$ ghc -O1 Sieve.hs && ./Sieve
[1 of 1] Compiling Main ( Sieve.hs, Sieve.o ) [Optimisation flags changed]
Linking Sieve ...
False
It reproduces on OS X and Ubuntu, but worked fine in GHC 8.2.
I looked into generated Core and found a suspicious function, having two __DEFAULT
cases with different bodies.
main2 :: String
main2
= case vec `cast` <Co:3> of
{ Vector ipv_sb7L ipv1_sb7M ipv2_sb7N ->
case <# 0# ipv1_sb7M of {
__DEFAULT -> case main3 ipv1_sb7M of wild_00 { };
1# ->
case indexIntArray# ipv2_sb7N ipv_sb7L of {
__DEFAULT -> $fShowBool4;
__DEFAULT -> $fShowBool2;
1# -> $fShowBool2;
2# -> $fShowBool2
}
}
}
Trac metadata
Trac field | Value |
---|---|
Version | 8.4.1-alpha3 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | high |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |