Unlifted datatypes not handled right in demand analysis/worker-wrapper
Summary
We're not unwrapping as I would expect.
Steps to reproduce
{-# language UnliftedDatatypes #-}
{-# language BangPatterns #-}
module UL where
import GHC.Exts (UnliftedType)
type Gram :: UnliftedType
data Gram = Gram !Int !Int
{-# NOINLINE yeah #-}
yeah :: Gram -> (Int, Int)
yeah g = (case g of Gram a _ -> a, case g of Gram _ b -> b)
data Foo = Foo !Int !Int
{-# NOINLINE bam #-}
bam :: Foo -> (Int, Int)
bam !f = (case f of Foo a _ -> a, case f of Foo _ b -> b)
Expected behavior
I would expect to get very similar workers and wrappers for yeah
and bam
, but that's not the case. bam
's wrapper unwraps Foo
and passes the Int#
s to the worker, which looks like this:
UL.$wbam [InlPrag=NOINLINE]
:: GHC.Prim.Int# -> GHC.Prim.Int# -> (# Int, Int #)
[GblId, Arity=2, Str=<L><L>, Unf=OtherCon []]
UL.$wbam
= \ (ww_sF1 :: GHC.Prim.Int#) (ww1_sF2 :: GHC.Prim.Int#) ->
(# GHC.Types.I# ww_sF1, GHC.Types.I# ww1_sF2 #)
yeah
's wrapper leaves Gram
intact, and we get a pretty funny looking worker:
UL.$wyeah [InlPrag=NOINLINE] :: Gram -> (# Int, Int #)
[GblId, Arity=1, Str=<LP(L,L)>, Unf=OtherCon []]
UL.$wyeah
= \ (w_sES :: Gram) ->
(# case w_sES of { Gram dt_dEx dt1_dEy -> GHC.Types.I# dt_dEx },
case w_sES of { Gram dt_dEz dt1_dEA -> GHC.Types.I# dt1_dEA } #)
Environment
- GHC version used: 9.2.1
Edited by David Feuer