DmdAnal and WorkWrap should support unboxing constructors with existentials (or even GADTs)
Both demand analysis and worker/wrapper currently don't cope with existentials, let alone GADTs:
{-# LANGUAGE GADTs #-}
module Lib where
data Box a where
Box :: a -> Box a
data Ex a where
Ex :: e -> a -> Ex a
data GADT a where
GADT :: Int -> GADT Int
f :: Box Int -> Int
f (Box n) = n
{-# NOINLINE f #-}
g :: Ex Int -> Int
g (Ex _ n) = n
{-# NOINLINE g #-}
h :: GADT a -> Int
h (GADT n) = n
{-# NOINLINE h #-}
This is the Core output you get:
$wf = \ ww_sxG -> ww_sxG
f = \ w_sxA ->
case w_sxA of { Box ww1_sxD ->
case ww1_sxD of { I# ww3_sxG ->
case $wf ww3_sxG of ww4_sxL { __DEFAULT -> I# ww4_sxL }
}
}
g = \ ds_dws ->
case ds_dws of { Ex @ e_avJ ds1_dwB n_aud -> n_aud }
$wh = \ @ a_sxO ww_sxS ww1_sxW -> ww1_sxW
h = \ @ a_sxO w_sxP ->
case w_sxP of { GADT ww1_sxS ww2_sxT ->
case ww2_sxT of { I# ww4_sxW ->
case $wh @~ <Co:1> ww4_sxW of ww5_sy1 { __DEFAULT -> I# ww5_sy1 }
}
}
To my surprise, the GADT in h
got properly unboxed! The existential constructor in g
not so much. I wonder why, GADT
seems strictly more complex than Ex
in its desugared form.