Simon Peyton Jones pushed to branch wip/T23559 at Glasgow Haskell Compiler / GHC
Commits:
f7dc61d5 by Simon Peyton Jones at 2025-11-26T23:26:35+00:00
Switch -fpolymorphic-specialisation on by default
This patch addresses #23559.
Now that !10479 has landed and #26329 is fixed, we can switch on
polymorphic specialisation by default, addressing a bunch of other
tickets listed in #23559.
Metric changes:
* CoOpt_Singleton: +4% compiler allocations: we just get more
specialisations
* info_table_map_perf: -20% decrease in compiler allocations.
This is caused by using -fno-specialise in ExactPrint.hs
Without that change we get a 4x blow-up in compile time;
see !15058 for details
Metric Decrease:
info_table_map_perf
Metric Increase:
CoOpt_Singletons
- - - - -
4 changed files:
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- docs/users_guide/using-optimisation.rst
- testsuite/tests/simplCore/should_compile/T8331.stderr
Changes:
=====================================
compiler/GHC/Driver/DynFlags.hs
=====================================
@@ -1268,6 +1268,7 @@ optLevelFlags -- see Note [Documenting optimisation flags]
, ([1,2], Opt_CfgBlocklayout) -- Experimental
, ([1,2], Opt_Specialise)
+ , ([1,2], Opt_PolymorphicSpecialisation) -- Now on by default (#23559)
, ([1,2], Opt_CrossModuleSpecialise)
, ([1,2], Opt_InlineGenerics)
, ([1,2], Opt_Strictness)
=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -909,6 +909,7 @@ optimisationFlags = EnumSet.fromList
, Opt_SpecialiseAggressively
, Opt_CrossModuleSpecialise
, Opt_StaticArgumentTransformation
+ , Opt_PolymorphicSpecialisation
, Opt_CSE
, Opt_StgCSE
, Opt_StgLiftLams
=====================================
docs/users_guide/using-optimisation.rst
=====================================
@@ -1325,10 +1325,7 @@ as such you shouldn't need to set any of them explicitly. A flag
:reverse: -fno-polymorphic-specialisation
:category:
- :default: off
-
- Warning, this feature is highly experimental and may lead to incorrect runtime
- results. Use at your own risk (:ghc-ticket:`23469`, :ghc-ticket:`23109`, :ghc-ticket:`21229`, :ghc-ticket:`23445`).
+ :default: on
Enable specialisation of function calls to known dictionaries with free type variables.
The created specialisation will abstract over the type variables free in the dictionary.
=====================================
testsuite/tests/simplCore/should_compile/T8331.stderr
=====================================
@@ -1,5 +1,148 @@
==================== Tidy Core rules ====================
+"SPEC $c*> @(ST s) @_"
+ forall (@s) (@r) ($dApplicative :: Applicative (ST s)).
+ $fApplicativeReaderT_$c*> @(ST s) @r $dApplicative
+ = ($fApplicativeReaderT2 @s @r)
+ `cast` (forall (a ::~ <*>_N) (b ::~ <*>_N).
+ _R
+ ->_R _R
+ ->_R <r>_R ->_R Sym (N:ST <s>_N <b>_R)
+ ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <b>_N)
+ :: Coercible
+ (forall a b.
+ ReaderT r (ST s) a -> ReaderT r (ST s) b -> r -> STRep s b)
+ (forall a b.
+ ReaderT r (ST s) a -> ReaderT r (ST s) b -> ReaderT r (ST s) b))
+"SPEC $c<$ @(ST s) @_"
+ forall (@s) (@r) ($dFunctor :: Functor (ST s)).
+ $fFunctorReaderT_$c<$ @(ST s) @r $dFunctor
+ = ($fApplicativeReaderT6 @s @r)
+ `cast` (forall (a ::~ <*>_N) (b ::~ <*>_N).
+ <a>_R
+ ->_R _R
+ ->_R <r>_R ->_R Sym (N:ST <s>_N <a>_R)
+ ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <a>_N)
+ :: Coercible
+ (forall a b. a -> ReaderT r (ST s) b -> r -> STRep s a)
+ (forall a b. a -> ReaderT r (ST s) b -> ReaderT r (ST s) a))
+"SPEC $c<* @(ST s) @_"
+ forall (@s) (@r) ($dApplicative :: Applicative (ST s)).
+ $fApplicativeReaderT_$c<* @(ST s) @r $dApplicative
+ = ($fApplicativeReaderT1 @s @r)
+ `cast` (forall (a ::~ <*>_N) (b ::~ <*>_N).
+ _R
+ ->_R _R
+ ->_R <r>_R ->_R Sym (N:ST <s>_N <a>_R)
+ ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <a>_N)
+ :: Coercible
+ (forall a b.
+ ReaderT r (ST s) a -> ReaderT r (ST s) b -> r -> STRep s a)
+ (forall a b.
+ ReaderT r (ST s) a -> ReaderT r (ST s) b -> ReaderT r (ST s) a))
+"SPEC $c<*> @(ST s) @_"
+ forall (@s) (@r) ($dApplicative :: Applicative (ST s)).
+ $fApplicativeReaderT9 @(ST s) @r $dApplicative
+ = ($fApplicativeReaderT4 @s @r)
+ `cast` (forall (a ::~ <*>_N) (b ::~ <*>_N).
+ b)>_R
+ ->_R _R
+ ->_R <r>_R
+ ->_R Sym (N:ST <s>_N <b>_R)
+ :: Coercible
+ (forall a b.
+ ReaderT r (ST s) (a -> b) -> ReaderT r (ST s) a -> r -> STRep s b)
+ (forall a b.
+ ReaderT r (ST s) (a -> b) -> ReaderT r (ST s) a -> r -> ST s b))
+"SPEC $c>> @(ST s) @_"
+ forall (@s) (@r) ($dMonad :: Monad (ST s)).
+ $fMonadReaderT1 @(ST s) @r $dMonad
+ = $fMonadAbstractIOSTReaderT_$s$c>> @s @r
+"SPEC $c>>= @(ST s) @_"
+ forall (@s) (@r) ($dMonad :: Monad (ST s)).
+ $fMonadReaderT2 @(ST s) @r $dMonad
+ = ($fMonadAbstractIOSTReaderT2 @s @r)
+ `cast` (forall (a ::~ <*>_N) (b ::~ <*>_N).
+ _R
+ ->_R ReaderT r (ST s) b>_R
+ ->_R <r>_R
+ ->_R Sym (N:ST <s>_N <b>_R)
+ :: Coercible
+ (forall a b.
+ ReaderT r (ST s) a -> (a -> ReaderT r (ST s) b) -> r -> STRep s b)
+ (forall a b.
+ ReaderT r (ST s) a -> (a -> ReaderT r (ST s) b) -> r -> ST s b))
+"SPEC $cfmap @(ST s) @_"
+ forall (@s) (@r) ($dFunctor :: Functor (ST s)).
+ $fFunctorReaderT_$cfmap @(ST s) @r $dFunctor
+ = ($fApplicativeReaderT7 @s @r)
+ `cast` (forall (a ::~ <*>_N) (b ::~ <*>_N).
+ b>_R
+ ->_R _R
+ ->_R <r>_R ->_R Sym (N:ST <s>_N <b>_R)
+ ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <b>_N)
+ :: Coercible
+ (forall a b. (a -> b) -> ReaderT r (ST s) a -> r -> STRep s b)
+ (forall a b. (a -> b) -> ReaderT r (ST s) a -> ReaderT r (ST s) b))
+"SPEC $cliftA2 @(ST s) @_"
+ forall (@s) (@r) ($dApplicative :: Applicative (ST s)).
+ $fApplicativeReaderT_$cliftA2 @(ST s) @r $dApplicative
+ = ($fApplicativeReaderT3 @s @r)
+ `cast` (forall (a ::~ <*>_N) (b ::~ <*>_N) (c ::~ <*>_N).
+ b -> c>_R
+ ->_R _R
+ ->_R _R
+ ->_R <r>_R ->_R Sym (N:ST <s>_N <c>_R)
+ ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <c>_N)
+ :: Coercible
+ (forall a b c.
+ (a -> b -> c)
+ -> ReaderT r (ST s) a -> ReaderT r (ST s) b -> r -> STRep s c)
+ (forall a b c.
+ (a -> b -> c)
+ -> ReaderT r (ST s) a -> ReaderT r (ST s) b -> ReaderT r (ST s) c))
+"SPEC $cp1Applicative @(ST s) @_"
+ forall (@s) (@r) ($dApplicative :: Applicative (ST s)).
+ $fApplicativeReaderT_$cp1Applicative @(ST s) @r $dApplicative
+ = $fApplicativeReaderT_$s$fFunctorReaderT @s @r
+"SPEC $cp1Monad @(ST s) @_"
+ forall (@s) (@r) ($dMonad :: Monad (ST s)).
+ $fMonadReaderT_$cp1Monad @(ST s) @r $dMonad
+ = $fApplicativeReaderT_$s$fApplicativeReaderT @s @r
+"SPEC $cpure @(ST s) @_"
+ forall (@s) (@r) ($dApplicative :: Applicative (ST s)).
+ $fApplicativeReaderT_$cpure @(ST s) @r $dApplicative
+ = ($fApplicativeReaderT5 @s @r)
+ `cast` (forall (a ::~ <*>_N).
+ <a>_R
+ ->_R <r>_R ->_R Sym (N:ST <s>_N <a>_R)
+ ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <a>_N)
+ :: Coercible
+ (forall a. a -> r -> STRep s a)
+ (forall a. a -> ReaderT r (ST s) a))
+"SPEC $creturn @(ST s) @_"
+ forall (@s) (@r) ($dMonad :: Monad (ST s)).
+ $fMonadReaderT_$creturn @(ST s) @r $dMonad
+ = ($fApplicativeReaderT5 @s @r)
+ `cast` (forall (a ::~ <*>_N).
+ <a>_R
+ ->_R <r>_R ->_R Sym (N:ST <s>_N <a>_R)
+ ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <a>_N)
+ :: Coercible
+ (forall a. a -> r -> STRep s a)
+ (forall a. a -> ReaderT r (ST s) a))
+"SPEC $fApplicativeReaderT @(ST s) @_"
+ forall (@s) (@r) ($dApplicative :: Applicative (ST s)).
+ $fApplicativeReaderT @(ST s) @r $dApplicative
+ = $fApplicativeReaderT_$s$fApplicativeReaderT @s @r
+"SPEC $fFunctorReaderT @(ST s) @_"
+ forall (@s) (@r) ($dFunctor :: Functor (ST s)).
+ $fFunctorReaderT @(ST s) @r $dFunctor
+ = $fApplicativeReaderT_$s$fFunctorReaderT @s @r
+"SPEC $fMonadReaderT @(ST s) @_"
+ forall (@s) (@r) ($dMonad :: Monad (ST s)).
+ $fMonadReaderT @(ST s) @r $dMonad
+ = $fMonadAbstractIOSTReaderT_$s$fMonadReaderT @s @r
"USPEC useAbstractMonad @(ReaderT Int (ST s))"
forall (@s)
($dMonadAbstractIOST :: MonadAbstractIOST (ReaderT Int (ST s))).
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f7dc61d5578bd052bded0e24fb84b0437035d43a
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f7dc61d5578bd052bded0e24fb84b0437035d43a
You're receiving this email because of your account on gitlab.haskell.org.