Suprising behavior of auto-specialization and Exts.inline
Summary
This behavior was found using GHC 9.6.3 -O1 and packages vector 0.13.1.0
and vector-algorithms 0.9.0.1
. I have not tested other versions, and I am also not sure how to get a smaller repro.
Consider the code
module M where
import Control.Monad.ST
import qualified Data.Vector as V -- from vector
import qualified Data.Vector.Mutable as VM -- from vector
import qualified Data.Vector.Algorithms.Merge as Merge -- from vector-algorithms
import GHC.Exts (inline)
fooST :: VM.MVector s Int -> ST s ()
fooST = Merge.sort
fooSTInline :: VM.MVector s Int -> ST s ()
fooSTInline = inline Merge.sort
fooSTRW :: VM.MVector RealWorld Int -> ST RealWorld ()
fooSTRW = Merge.sort
Merge.sort
is a function marked INLINABLE
. The source can be seen here on Hackage.
Observed behavior:
-
fooST
does not specialize. The Core looks like:
-- RHS size: {terms: 5, types: 7, coercions: 0, joins: 0/0}
M.fooST1
:: forall {s}. VM.MVector (VM.PrimState (ST s)) Int -> ST s ()
[GblId,
Unf=Unf{Src=<vanilla>, TopLvl=True,
Value=False, ConLike=False, WorkFree=False, Expandable=True,
Guidance=IF_ARGS [] 40 0}]
M.fooST1
= \ (@s) ->
Merge.sort
@(ST s)
@VM.MVector
@Int
(Control.Monad.Primitive.$fPrimMonadST0 @s)
(Data.Vector.Mutable.$fMVectorMVectora @Int)
ghc-prim:GHC.Classes.$fOrdInt
-- RHS size: {terms: 1, types: 0, coercions: 11, joins: 0/0}
fooST :: forall s. VM.MVector s Int -> ST s ()
[GblId,
Unf=Unf{Src=<vanilla>, TopLvl=True,
Value=False, ConLike=False, WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=True)}]
fooST
= M.fooST1
`cast` (forall (s :: <*>_N).
(VM.MVector
(Control.Monad.Primitive.D:R:PrimStateST0[0] <s>_N) <Int>_R)_R
%<Many>_N ->_R <ST s ()>_R
:: (forall {s}. VM.MVector (VM.PrimState (ST s)) Int -> ST s ())
~R# (forall {s}. VM.MVector s Int -> ST s ()))
- In
fooSTInline
,Merge.sort
does not get inlined. The Core looks like:
-- RHS size: {terms: 1, types: 0, coercions: 11, joins: 0/0}
fooSTInline :: forall s. VM.MVector s Int -> ST s ()
[GblId,
Unf=Unf{Src=<vanilla>, TopLvl=True,
Value=False, ConLike=False, WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=True)}]
fooSTInline
= M.fooST1
`cast` (forall (s :: <*>_N).
(VM.MVector
(Control.Monad.Primitive.D:R:PrimStateST0[0] <s>_N) <Int>_R)_R
%<Many>_N ->_R <ST s ()>_R
:: (forall {s}. VM.MVector (VM.PrimState (ST s)) Int -> ST s ())
~R# (forall {s}. VM.MVector s Int -> ST s ()))
-
fooSTRW
does specialize. The Core is below, where$ssort
is the specializedsort
.
-- RHS size: {terms: 1, types: 0, coercions: 10, joins: 0/0}
fooSTRW :: VM.MVector RealWorld Int -> ST RealWorld ()
[GblId,
Arity=2,
Str=<1!P(L,L,L)><L>,
Cpr=1(, 1),
Unf=Unf{Src=<vanilla>, TopLvl=True,
Value=True, ConLike=True, WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=True)}]
fooSTRW
= M.$ssort
`cast` ((VM.MVector
(Control.Monad.Primitive.D:R:PrimStateST0[0] <RealWorld>_N)
<Int>_R)_R
%<Many>_N ->_R Sym (GHC.ST.N:ST[0] <RealWorld>_N <()>_R)
:: (VM.MVector (VM.PrimState (ST RealWorld)) Int
-> GHC.ST.STRep RealWorld ())
~R# (VM.MVector RealWorld Int -> ST RealWorld ()))
Steps to reproduce
Compile the above and check the Core.
Expected behavior
- If
fooSTRW
specializes, so shouldfooST
. - In
fooSTInline
,Merge.sort
should inline.
Environment
- GHC version used: 9.6.3, 9.8.2, 9.10.1-rc1
Edited by meooow