Ben Gamari pushed to branch wip/backports-9.14 at Glasgow Haskell Compiler / GHC

Commits:

5 changed files:

Changes:

  • compiler/GHC/Driver/DynFlags.hs
    ... ... @@ -1250,6 +1250,7 @@ optLevelFlags -- see Note [Documenting optimisation flags]
    1250 1250
         , ([1,2],   Opt_CfgBlocklayout)      -- Experimental
    
    1251 1251
     
    
    1252 1252
         , ([1,2],   Opt_Specialise)
    
    1253
    +    , ([1,2],   Opt_PolymorphicSpecialisation)
    
    1253 1254
         , ([1,2],   Opt_CrossModuleSpecialise)
    
    1254 1255
         , ([1,2],   Opt_InlineGenerics)
    
    1255 1256
         , ([1,2],   Opt_Strictness)
    

  • compiler/GHC/Driver/Flags.hs
    ... ... @@ -907,6 +907,7 @@ optimisationFlags = EnumSet.fromList
    907 907
        , Opt_SpecialiseAggressively
    
    908 908
        , Opt_CrossModuleSpecialise
    
    909 909
        , Opt_StaticArgumentTransformation
    
    910
    +   , Opt_PolymorphicSpecialisation
    
    910 911
        , Opt_CSE
    
    911 912
        , Opt_StgCSE
    
    912 913
        , Opt_StgLiftLams
    

  • docs/users_guide/9.14.1-notes.rst
    ... ... @@ -102,7 +102,9 @@ Language
    102 102
     Compiler
    
    103 103
     ~~~~~~~~
    
    104 104
     
    
    105
    -- An improved error message is introduced to refer users to the heap-controlling flags of the RTS when there is a heap overflow during compilation. (#25198)
    
    105
    +- Polymorphic specialisation has been reenabled by default in optimisation levels 1 and higher (:ghc-ticket:`23559`)
    
    106
    +
    
    107
    +- An improved error message is introduced to refer users to the heap-controlling flags of the RTS when there is a heap overflow during compilation. (:ghc-ticket:`25198`)
    
    106 108
     
    
    107 109
     - The kind checker now does a better job of finding type family instances for
    
    108 110
       use in the kinds of other declarations in the same module. This fixes a number
    
    ... ... @@ -116,14 +118,14 @@ Compiler
    116 118
       subordinate import lists (:ghc-ticket:`22581`).
    
    117 119
     
    
    118 120
     - A new flag, :ghc-flag:`-Wuseless-specialisations`, controls warnings emitted when GHC
    
    119
    -  determines that a SPECIALISE pragma would have no effect.
    
    121
    +  determines that a ``SPECIALISE`` pragma would have no effect.
    
    120 122
     
    
    121
    -- A new flag, :ghc-flag:`-Wrule-lhs-equalities`, controls warnings emitted for RULES
    
    123
    +- A new flag, :ghc-flag:`-Wrule-lhs-equalities`, controls warnings emitted for ``RULES``
    
    122 124
       whose left-hand side attempts to quantify over equality constraints that
    
    123 125
       previous GHC versions accepted quantifying over. GHC will now drop such RULES,
    
    124 126
       emitting a warning message controlled by this flag.
    
    125 127
     
    
    126
    -  This warning is intended to give visibility to the fact that the RULES that
    
    128
    +  This warning is intended to give visibility to the fact that the ``RULES`` that
    
    127 129
       previous GHC versions generated in such circumstances could never fire.
    
    128 130
     
    
    129 131
     - A new flag, :ghc-flag:`-Wunusable-unpack-pragmas`, controls warnings emitted
    

  • docs/users_guide/using-optimisation.rst
    ... ... @@ -1316,10 +1316,7 @@ as such you shouldn't need to set any of them explicitly. A flag
    1316 1316
         :reverse: -fno-polymorphic-specialisation
    
    1317 1317
         :category:
    
    1318 1318
     
    
    1319
    -    :default: off
    
    1320
    -
    
    1321
    -    Warning, this feature is highly experimental and may lead to incorrect runtime
    
    1322
    -    results. Use at your own risk (:ghc-ticket:`23469`, :ghc-ticket:`23109`, :ghc-ticket:`21229`, :ghc-ticket:`23445`).
    
    1319
    +    :default: on
    
    1323 1320
     
    
    1324 1321
         Enable specialisation of function calls to known dictionaries with free type variables.
    
    1325 1322
         The created specialisation will abstract over the type variables free in the dictionary.
    

  • testsuite/tests/simplCore/should_compile/T8331.stderr
    1 1
     
    
    2 2
     ==================== Tidy Core rules ====================
    
    3
    +"SPEC $c*> @(ST s) @_"
    
    4
    +    forall (@s) (@r) ($dApplicative :: Applicative (ST s)).
    
    5
    +      $fApplicativeReaderT_$c*> @(ST s) @r $dApplicative
    
    6
    +      = ($fApplicativeReaderT2 @s @r)
    
    7
    +        `cast` (forall (a :: <*>_N) (b :: <*>_N).
    
    8
    +                <ReaderT r (ST s) a>_R
    
    9
    +                %<'Many>_N ->_R <ReaderT r (ST s) b>_R
    
    10
    +                %<'Many>_N ->_R <r>_R %<'Many>_N ->_R Sym (N:ST <s>_N <b>_R)
    
    11
    +                                ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <b>_N)
    
    12
    +                :: Coercible
    
    13
    +                     (forall a b.
    
    14
    +                      ReaderT r (ST s) a -> ReaderT r (ST s) b -> r -> STRep s b)
    
    15
    +                     (forall a b.
    
    16
    +                      ReaderT r (ST s) a -> ReaderT r (ST s) b -> ReaderT r (ST s) b))
    
    17
    +"SPEC $c<$ @(ST s) @_"
    
    18
    +    forall (@s) (@r) ($dFunctor :: Functor (ST s)).
    
    19
    +      $fFunctorReaderT_$c<$ @(ST s) @r $dFunctor
    
    20
    +      = ($fApplicativeReaderT6 @s @r)
    
    21
    +        `cast` (forall (a :: <*>_N) (b :: <*>_N).
    
    22
    +                <a>_R
    
    23
    +                %<'Many>_N ->_R <ReaderT r (ST s) b>_R
    
    24
    +                %<'Many>_N ->_R <r>_R %<'Many>_N ->_R Sym (N:ST <s>_N <a>_R)
    
    25
    +                                ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <a>_N)
    
    26
    +                :: Coercible
    
    27
    +                     (forall a b. a -> ReaderT r (ST s) b -> r -> STRep s a)
    
    28
    +                     (forall a b. a -> ReaderT r (ST s) b -> ReaderT r (ST s) a))
    
    29
    +"SPEC $c<* @(ST s) @_"
    
    30
    +    forall (@s) (@r) ($dApplicative :: Applicative (ST s)).
    
    31
    +      $fApplicativeReaderT_$c<* @(ST s) @r $dApplicative
    
    32
    +      = ($fApplicativeReaderT1 @s @r)
    
    33
    +        `cast` (forall (a :: <*>_N) (b :: <*>_N).
    
    34
    +                <ReaderT r (ST s) a>_R
    
    35
    +                %<'Many>_N ->_R <ReaderT r (ST s) b>_R
    
    36
    +                %<'Many>_N ->_R <r>_R %<'Many>_N ->_R Sym (N:ST <s>_N <a>_R)
    
    37
    +                                ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <a>_N)
    
    38
    +                :: Coercible
    
    39
    +                     (forall a b.
    
    40
    +                      ReaderT r (ST s) a -> ReaderT r (ST s) b -> r -> STRep s a)
    
    41
    +                     (forall a b.
    
    42
    +                      ReaderT r (ST s) a -> ReaderT r (ST s) b -> ReaderT r (ST s) a))
    
    43
    +"SPEC $c<*> @(ST s) @_"
    
    44
    +    forall (@s) (@r) ($dApplicative :: Applicative (ST s)).
    
    45
    +      $fApplicativeReaderT9 @(ST s) @r $dApplicative
    
    46
    +      = ($fApplicativeReaderT4 @s @r)
    
    47
    +        `cast` (forall (a :: <*>_N) (b :: <*>_N).
    
    48
    +                <ReaderT r (ST s) (a -> b)>_R
    
    49
    +                %<'Many>_N ->_R <ReaderT r (ST s) a>_R
    
    50
    +                %<'Many>_N ->_R <r>_R
    
    51
    +                %<'Many>_N ->_R Sym (N:ST <s>_N <b>_R)
    
    52
    +                :: Coercible
    
    53
    +                     (forall a b.
    
    54
    +                      ReaderT r (ST s) (a -> b) -> ReaderT r (ST s) a -> r -> STRep s b)
    
    55
    +                     (forall a b.
    
    56
    +                      ReaderT r (ST s) (a -> b) -> ReaderT r (ST s) a -> r -> ST s b))
    
    57
    +"SPEC $c>> @(ST s) @_"
    
    58
    +    forall (@s) (@r) ($dMonad :: Monad (ST s)).
    
    59
    +      $fMonadReaderT1 @(ST s) @r $dMonad
    
    60
    +      = $fMonadAbstractIOSTReaderT_$s$c>> @s @r
    
    61
    +"SPEC $c>>= @(ST s) @_"
    
    62
    +    forall (@s) (@r) ($dMonad :: Monad (ST s)).
    
    63
    +      $fMonadReaderT2 @(ST s) @r $dMonad
    
    64
    +      = ($fMonadAbstractIOSTReaderT2 @s @r)
    
    65
    +        `cast` (forall (a :: <*>_N) (b :: <*>_N).
    
    66
    +                <ReaderT r (ST s) a>_R
    
    67
    +                %<'Many>_N ->_R <a -> ReaderT r (ST s) b>_R
    
    68
    +                %<'Many>_N ->_R <r>_R
    
    69
    +                %<'Many>_N ->_R Sym (N:ST <s>_N <b>_R)
    
    70
    +                :: Coercible
    
    71
    +                     (forall a b.
    
    72
    +                      ReaderT r (ST s) a -> (a -> ReaderT r (ST s) b) -> r -> STRep s b)
    
    73
    +                     (forall a b.
    
    74
    +                      ReaderT r (ST s) a -> (a -> ReaderT r (ST s) b) -> r -> ST s b))
    
    75
    +"SPEC $cfmap @(ST s) @_"
    
    76
    +    forall (@s) (@r) ($dFunctor :: Functor (ST s)).
    
    77
    +      $fFunctorReaderT_$cfmap @(ST s) @r $dFunctor
    
    78
    +      = ($fApplicativeReaderT7 @s @r)
    
    79
    +        `cast` (forall (a :: <*>_N) (b :: <*>_N).
    
    80
    +                <a -> b>_R
    
    81
    +                %<'Many>_N ->_R <ReaderT r (ST s) a>_R
    
    82
    +                %<'Many>_N ->_R <r>_R %<'Many>_N ->_R Sym (N:ST <s>_N <b>_R)
    
    83
    +                                ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <b>_N)
    
    84
    +                :: Coercible
    
    85
    +                     (forall a b. (a -> b) -> ReaderT r (ST s) a -> r -> STRep s b)
    
    86
    +                     (forall a b. (a -> b) -> ReaderT r (ST s) a -> ReaderT r (ST s) b))
    
    87
    +"SPEC $cliftA2 @(ST s) @_"
    
    88
    +    forall (@s) (@r) ($dApplicative :: Applicative (ST s)).
    
    89
    +      $fApplicativeReaderT_$cliftA2 @(ST s) @r $dApplicative
    
    90
    +      = ($fApplicativeReaderT3 @s @r)
    
    91
    +        `cast` (forall (a :: <*>_N) (b :: <*>_N) (c :: <*>_N).
    
    92
    +                <a -> b -> c>_R
    
    93
    +                %<'Many>_N ->_R <ReaderT r (ST s) a>_R
    
    94
    +                %<'Many>_N ->_R <ReaderT r (ST s) b>_R
    
    95
    +                %<'Many>_N ->_R <r>_R %<'Many>_N ->_R Sym (N:ST <s>_N <c>_R)
    
    96
    +                                ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <c>_N)
    
    97
    +                :: Coercible
    
    98
    +                     (forall a b c.
    
    99
    +                      (a -> b -> c)
    
    100
    +                      -> ReaderT r (ST s) a -> ReaderT r (ST s) b -> r -> STRep s c)
    
    101
    +                     (forall a b c.
    
    102
    +                      (a -> b -> c)
    
    103
    +                      -> ReaderT r (ST s) a -> ReaderT r (ST s) b -> ReaderT r (ST s) c))
    
    104
    +"SPEC $cp1Applicative @(ST s) @_"
    
    105
    +    forall (@s) (@r) ($dApplicative :: Applicative (ST s)).
    
    106
    +      $fApplicativeReaderT_$cp1Applicative @(ST s) @r $dApplicative
    
    107
    +      = $fApplicativeReaderT_$s$fFunctorReaderT @s @r
    
    108
    +"SPEC $cp1Monad @(ST s) @_"
    
    109
    +    forall (@s) (@r) ($dMonad :: Monad (ST s)).
    
    110
    +      $fMonadReaderT_$cp1Monad @(ST s) @r $dMonad
    
    111
    +      = $fApplicativeReaderT_$s$fApplicativeReaderT @s @r
    
    112
    +"SPEC $cpure @(ST s) @_"
    
    113
    +    forall (@s) (@r) ($dApplicative :: Applicative (ST s)).
    
    114
    +      $fApplicativeReaderT_$cpure @(ST s) @r $dApplicative
    
    115
    +      = ($fApplicativeReaderT5 @s @r)
    
    116
    +        `cast` (forall (a :: <*>_N).
    
    117
    +                <a>_R
    
    118
    +                %<'Many>_N ->_R <r>_R %<'Many>_N ->_R Sym (N:ST <s>_N <a>_R)
    
    119
    +                                ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <a>_N)
    
    120
    +                :: Coercible
    
    121
    +                     (forall a. a -> r -> STRep s a)
    
    122
    +                     (forall a. a -> ReaderT r (ST s) a))
    
    123
    +"SPEC $creturn @(ST s) @_"
    
    124
    +    forall (@s) (@r) ($dMonad :: Monad (ST s)).
    
    125
    +      $fMonadReaderT_$creturn @(ST s) @r $dMonad
    
    126
    +      = ($fApplicativeReaderT5 @s @r)
    
    127
    +        `cast` (forall (a :: <*>_N).
    
    128
    +                <a>_R
    
    129
    +                %<'Many>_N ->_R <r>_R %<'Many>_N ->_R Sym (N:ST <s>_N <a>_R)
    
    130
    +                                ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <a>_N)
    
    131
    +                :: Coercible
    
    132
    +                     (forall a. a -> r -> STRep s a)
    
    133
    +                     (forall a. a -> ReaderT r (ST s) a))
    
    134
    +"SPEC $fApplicativeReaderT @(ST s) @_"
    
    135
    +    forall (@s) (@r) ($dApplicative :: Applicative (ST s)).
    
    136
    +      $fApplicativeReaderT @(ST s) @r $dApplicative
    
    137
    +      = $fApplicativeReaderT_$s$fApplicativeReaderT @s @r
    
    138
    +"SPEC $fFunctorReaderT @(ST s) @_"
    
    139
    +    forall (@s) (@r) ($dFunctor :: Functor (ST s)).
    
    140
    +      $fFunctorReaderT @(ST s) @r $dFunctor
    
    141
    +      = $fApplicativeReaderT_$s$fFunctorReaderT @s @r
    
    142
    +"SPEC $fMonadReaderT @(ST s) @_"
    
    143
    +    forall (@s) (@r) ($dMonad :: Monad (ST s)).
    
    144
    +      $fMonadReaderT @(ST s) @r $dMonad
    
    145
    +      = $fMonadAbstractIOSTReaderT_$s$fMonadReaderT @s @r
    
    3 146
     "USPEC useAbstractMonad @(ReaderT Int (ST s))"
    
    4 147
         forall (@s)
    
    5 148
                ($dMonadAbstractIOST :: MonadAbstractIOST (ReaderT Int (ST s))).