Skip to content

WorkWrap should eliminate unlifted absent coercions

From #18982 (closed):

{-# LANGUAGE GADTs #-}

module Lib where

data GADT a where
  GADT :: Int -> GADT Int

h :: GADT a -> Int
h (GADT n) = n
{-# NOINLINE h #-}

produces

Lib.$wh [InlPrag=NOINLINE]
  :: forall a. (a GHC.Prim.~# Int) -> GHC.Prim.Int# -> GHC.Prim.Int#
Lib.$wh
  = \ (@ a_sxO)
      (ww_sxS [Dmd=<L,A>] :: a_sxO GHC.Prim.~# Int)
      (ww1_sxW :: GHC.Prim.Int#) ->
      ww1_sxW

-- RHS size: {terms: 14, types: 18, coercions: 1, joins: 0/0}
h [InlPrag=NOUSERINLINE[0]] :: forall a. GADT a -> Int
h = \ (@ a_sxO) (w_sxP :: GADT a_sxO) ->
      case w_sxP of { GADT ww1_sxS [Dmd=<L,A>] ww2_sxT ->
      case ww2_sxT of { GHC.Types.I# ww4_sxW ->
      case Lib.$wh @ a_sxO @~ (ww1_sxS :: a_sxO GHC.Prim.~# Int) ww4_sxW
      of ww5_sy1
      { __DEFAULT ->
      GHC.Types.I# ww5_sy1
      }
      }
      }

The coercion argument to the worker $wh is absent, but still present in the simplified code. It would be good if we can change that, as it also makes the type argument @a dead. Then we end up with a much simpler worker and call site.

Not that it would not impact runtime performance other than maybe through inlining decisions.

I think the problem has to do with "what kind of absent dummy should we pick for the coercion type?".

Edited by Sebastian Graf
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information