Unpacked sums lose strict field information after construction.
Summary
{-# OPTIONS_GHC -ddump-stg-final -ddump-to-file #-}
module M where
-- Strict Maybe
data SM a = SN | SJ !a
data Foo = Foo !(SM Bool)
bar :: Foo -> Bool
bar (Foo SN) = False
bar (Foo (SJ False)) = True
bar (Foo (SJ True)) = False
{-# NOINLINE bar #-}
-- Same as Foo but unpack the SM
data Foo2 = Foo2 {-# UNPACK #-} !(SM Bool)
bar2 :: Foo2 -> Bool
bar2 (Foo2 SN) = False
bar2 (Foo2 (SJ False)) = True
bar2 (Foo2 (SJ True)) = False
{-# NOINLINE bar2 #-}
This outputs the STG
M.$wbar [InlPrag=NOINLINE] :: M.SM GHC.Types.Bool -> GHC.Types.Bool
[GblId[StrictWorker([!])], Arity=1, Str=<1L>, Unf=OtherCon []] =
{} \r [ww_sAH]
case ww_sAH<TagProper> of wild_sAI {
M.SN -> GHC.Types.False [];
M.SJ ds_sAJ [Occ=Once1!] ->
case ds_sAJ<TagProper> of wild1_sAK { -- !! has TagProper
GHC.Types.False -> GHC.Types.True [];
GHC.Types.True -> GHC.Types.False [];
};
};
M.bar [InlPrag=NOINLINE[final]] :: M.Foo -> GHC.Types.Bool
[GblId, Arity=1, Str=<1!P(1L)>, Unf=OtherCon []] =
{} \r [ds_sAL]
case ds_sAL of wild_sAM {
M.Foo ww_sAN [Occ=Once1] -> M.$wbar ww_sAN;
};
M.$wbar2 [InlPrag=NOINLINE]
:: (# (# #) | GHC.Types.Bool #) -> GHC.Types.Bool
[GblId[StrictWorker([])], Arity=1, Str=<1L>, Unf=OtherCon []] =
{} \r [us_gB1 us_gB2]
case us_gB1<TagProper> of tag_gB3 {
__DEFAULT -> GHC.Types.False [];
2# ->
case us_gB2 of ds_sAS { -- !! missing TagProper
GHC.Types.False -> GHC.Types.True [];
GHC.Types.True -> GHC.Types.False [];
};
};
Steps to reproduce
Compile the above code.
Expected behavior
I would expect to see a TagProper in $wbar2 as well.
Environment
- GHC version used: 9.12.2