Simon Peyton Jones pushed to branch wip/spj-try-opt-coercion at Glasgow Haskell Compiler / GHC

Commits:

13 changed files:

Changes:

  • compiler/GHC/Core/Coercion.hs
    ... ... @@ -2041,7 +2041,7 @@ This follows the lifting context extension definition in the
    2041 2041
     -- ----------------------------------------------------
    
    2042 2042
     
    
    2043 2043
     data LiftingContext = LC Subst LiftCoEnv
    
    2044
    -  -- in optCoercion, we need to lift when optimizing InstCo.
    
    2044
    +  -- In optCoercion, we need to lift when optimizing InstCo.
    
    2045 2045
       -- See Note [Optimising InstCo] in GHC.Core.Coercion.Opt
    
    2046 2046
       -- We thus propagate the substitution from GHC.Core.Coercion.Opt here.
    
    2047 2047
     
    

  • compiler/GHC/Core/Coercion/Opt.hs
    1 1
     -- (c) The University of Glasgow 2006
    
    2 2
     {-# LANGUAGE CPP #-}
    
    3 3
     
    
    4
    -module GHC.Core.Coercion.Opt
    
    5
    -   ( optCoProgram, optCoercion
    
    6
    -   , OptCoercionOpts (..)
    
    7
    -   )
    
    4
    +module GHC.Core.Coercion.Opt( optCoProgram )
    
    8 5
     where
    
    9 6
     
    
    10 7
     import GHC.Prelude
    
    ... ... @@ -44,19 +41,25 @@ import Control.Monad ( zipWithM )
    44 41
     
    
    45 42
     Note [Coercion optimisation]
    
    46 43
     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    47
    -This module does coercion optimisation.  See the paper
    
    44
    +This module does coercion optimisation.  The purpose is to reduce the size
    
    45
    +of the coercions that the compiler carries around -- they are just proofs,
    
    46
    +and serve no runtime need. So the purpose of coercion optimisation is simply
    
    47
    +to shrink coercions and thereby reduce compile time.
    
    48
    +
    
    49
    +See the paper
    
    48 50
        Evidence normalization in Systtem FV (RTA'13)
    
    49 51
        https://simon.peytonjones.org/evidence-normalization/
    
    50 52
     The paper is also in the GHC repo, in docs/opt-coercion.
    
    51 53
     
    
    52
    -However, although powerful and occasionally very effective, coercion optimisation
    
    53
    -can be very expensive (#26679).  So we apply it sparingly:
    
    54
    +However, although powerful and occasionally very effective, coercion
    
    55
    +optimisation can itself be very expensive (#26679).  So we apply it sparingly:
    
    54 56
     
    
    55 57
     * In the Simplifier, function `rebuild_go`, we use `isReflexiveCo` (which
    
    56 58
       computes the type of the coercion) to eliminate reflexive coercion, just
    
    57 59
       before we build a cast (e |> co).
    
    58 60
     
    
    59
    -  (More precisely, we use `isReflexiveCoIgnoringMultiplicity.)
    
    61
    +  (More precisely, we use `isReflexiveCoIgnoringMultiplicity;
    
    62
    +   c.f. GHC.Core.Coercion.Opt.opt_univ.)
    
    60 63
     
    
    61 64
     * We have a whole pass, `optCoProgram` that runs the coercion optimiser on all
    
    62 65
       the coercions in the program.
    
    ... ... @@ -66,6 +69,7 @@ can be very expensive (#26679). So we apply it sparingly:
    66 69
     
    
    67 70
       - We run it early in the optimisation pipeline
    
    68 71
         (see GHC.Core.Opt.Pipeline.getCoreToDo).
    
    72
    +    Controlled by a flag `-fopt-coercion`, on by default
    
    69 73
     
    
    70 74
     
    
    71 75
     Note [Optimising coercion optimisation]
    
    ... ... @@ -218,7 +222,7 @@ optCoExpr is (Case e b ty alts) = Case (optCoExpr is e) b ty
    218 222
                                            (map (optCoAlt (is `extendInScopeSet` b)) alts)
    
    219 223
     
    
    220 224
     optCo :: InScopeSet -> Coercion -> Coercion
    
    221
    -optCo is co = optCoercion' (mkEmptySubst is) co
    
    225
    +optCo is co = optCoercion (mkEmptySubst is) co
    
    222 226
     
    
    223 227
     optCoAlt :: InScopeSet -> CoreAlt -> CoreAlt
    
    224 228
     optCoAlt is (Alt k bs e)
    
    ... ... @@ -231,35 +235,13 @@ optCoAlt is (Alt k bs e)
    231 235
     %*                                                                      *
    
    232 236
     %********************************************************************* -}
    
    233 237
     
    
    234
    --- | Coercion optimisation options
    
    235
    -newtype OptCoercionOpts = OptCoercionOpts
    
    236
    -   { optCoercionEnabled :: Bool  -- ^ Enable coercion optimisation (reduce its size)
    
    237
    -   }
    
    238
    -
    
    239
    -optCoercion :: OptCoercionOpts -> Subst -> Coercion -> NormalCo
    
    238
    +optCoercion :: Subst -> Coercion -> NormalCo
    
    240 239
     -- ^ optCoercion applies a substitution to a coercion,
    
    241 240
     --   *and* optimises it to reduce its size
    
    242
    -optCoercion opts env co
    
    243
    --- Experiment with no optCoercion at all
    
    244
    -  | optCoercionEnabled opts
    
    245
    -  = if False then optCoercion' env co
    
    246
    -             else substCo env co
    
    247
    -
    
    248
    -{-
    
    249
    -  = pprTrace "optCoercion {" (text "Co:" <> ppr co) $
    
    250
    -    let result = optCoercion' env co in
    
    251
    -    pprTrace "optCoercion }"
    
    252
    -       (vcat [ text "Co:"    <+> ppr (coercionSize co)
    
    253
    -             , text "Optco:" <+> ppWhen (isReflCo result) (text "(refl)")
    
    254
    -                             <+> ppr result ]) $
    
    255
    -    result
    
    256
    --}
    
    257
    -
    
    258
    -  | otherwise
    
    259
    -  = substCo env co
    
    260
    -
    
    261
    -optCoercion' :: Subst -> Coercion -> NormalCo
    
    262
    -optCoercion' env co
    
    241
    +-- The substitution is a vestige of an earlier era, when the coercion optimiser
    
    242
    +--   was called by the Simplifier; now it is always empty
    
    243
    +--   But I have not removed it in case we ever want it back.
    
    244
    +optCoercion env co
    
    263 245
       | debugIsOn
    
    264 246
       = let out_co = opt_co1 lc NotSwapped co
    
    265 247
             (Pair in_ty1  in_ty2,  in_role)  = coercionKindRole co
    

  • compiler/GHC/Core/Opt/Pipeline.hs
    ... ... @@ -224,10 +224,12 @@ getCoreToDo dflags hpt_rule_base extra_vars
    224 224
             CoreDoPasses [ simpl_gently
    
    225 225
                          , runWhen do_specialise CoreDoSpecialising ],
    
    226 226
     
    
    227
    -        -- Optimise coercions
    
    227
    +        -- Optimise coercions: see Note [Coercion optimisation]
    
    228
    +        --                         in GHC.Core.Coercion.Opt
    
    228 229
             -- With -O do this after one run of the Simplifier.
    
    229 230
             -- Without -O, just take what the desugarer produced
    
    230
    -        -- See Note [Coercion optimisation] in GHC.Core.Coercion.Opt
    
    231
    +        -- I tried running it right after desugaring, regardless of -O,
    
    232
    +        -- but that was worse (longer compile times).
    
    231 233
             runWhen do_co_opt CoreOptCoercion,
    
    232 234
     
    
    233 235
             if full_laziness then
    

  • compiler/GHC/Core/Opt/Simplify/Env.hs
    ... ... @@ -15,7 +15,7 @@ module GHC.Core.Opt.Simplify.Env (
    15 15
             SimplPhase(..), isActive,
    
    16 16
             seArityOpts, seCaseCase, seCaseFolding, seCaseMerge, seCastSwizzle,
    
    17 17
             seDoEtaReduction, seEtaExpand, seFloatEnable, seInline, seNames,
    
    18
    -        seOptCoercionOpts, sePhase, sePlatform, sePreInline,
    
    18
    +        sePhase, sePlatform, sePreInline,
    
    19 19
             seRuleOpts, seRules, seUnfoldingOpts,
    
    20 20
             mkSimplEnv, extendIdSubst, extendCvIdSubst,
    
    21 21
             extendTvSubst, extendCvSubst,
    
    ... ... @@ -54,7 +54,6 @@ module GHC.Core.Opt.Simplify.Env (
    54 54
     
    
    55 55
     import GHC.Prelude
    
    56 56
     
    
    57
    -import GHC.Core.Coercion.Opt ( OptCoercionOpts )
    
    58 57
     import GHC.Core.FamInstEnv ( FamInstEnv )
    
    59 58
     import GHC.Core.Opt.Arity ( ArityOpts(..) )
    
    60 59
     import GHC.Core.Opt.Simplify.Monad
    
    ... ... @@ -250,9 +249,6 @@ seInline env = sm_inline (seMode env)
    250 249
     seNames :: SimplEnv -> [String]
    
    251 250
     seNames env = sm_names (seMode env)
    
    252 251
     
    
    253
    -seOptCoercionOpts :: SimplEnv -> OptCoercionOpts
    
    254
    -seOptCoercionOpts env = sm_co_opt_opts (seMode env)
    
    255
    -
    
    256 252
     sePhase :: SimplEnv -> SimplPhase
    
    257 253
     sePhase env = sm_phase (seMode env)
    
    258 254
     
    
    ... ... @@ -288,7 +284,6 @@ data SimplMode = SimplMode -- See comments in GHC.Core.Opt.Simplify.Monad
    288 284
       , sm_rule_opts :: !RuleOpts
    
    289 285
       , sm_case_folding :: !Bool
    
    290 286
       , sm_case_merge :: !Bool
    
    291
    -  , sm_co_opt_opts :: !OptCoercionOpts -- ^ Coercion optimiser options
    
    292 287
       }
    
    293 288
     
    
    294 289
     -- | See Note [SimplPhase]
    

  • compiler/GHC/Core/Opt/Simplify/Iteration.hs
    ... ... @@ -1531,8 +1531,10 @@ rebuild_go env expr cont
    1531 1531
           TickIt t cont    -> rebuild_go env (mkTick t expr) cont
    
    1532 1532
           CastIt { sc_co = co, sc_cont = cont }
    
    1533 1533
             | isReflexiveCoIgnoringMultiplicity co
    
    1534
    -              -- ignoring multiplicity: c.f. GHC.Core.Coercion.Opt.opt_univ
    
    1534
    +          -- isReflexiveCo: see Note [Coercion optimisation]
    
    1535
    +          --                in GHc.Core.Coercion.Opt
    
    1535 1536
             -> rebuild_go env expr cont
    
    1537
    +
    
    1536 1538
             | otherwise
    
    1537 1539
             -> rebuild_go env (mkCast expr co) cont
    
    1538 1540
                -- NB: mkCast implements the (Coercion co |> g) optimisation
    

  • compiler/GHC/Core/Rules.hs
    ... ... @@ -852,17 +852,17 @@ bound on the LHS:
    852 852
       Now, if that binding is inlined, so that a=b=Int, we'd get
    
    853 853
         RULE forall (c :: Int~Int). f (x |> c) = e
    
    854 854
       and now when we simplify the LHS (GHC.Core.Opt.Simplify.Iteration.simplRules),
    
    855
    -  optCoercion (look at the CoVarCo case) will turn that 'c' into Refl:
    
    855
    +  the Simplifier will turn that 'c' into Refl:
    
    856 856
         RULE forall (c :: Int~Int). f (x |> <Int>) = e
    
    857 857
       and then perhaps drop it altogether.  Now 'c' is unbound.
    
    858
    +  (See the use of isReflexiveCo in GHC.Core.Opt.Simplify.Iteration.)
    
    858 859
     
    
    859
    -  It's tricky to be sure this never happens, so instead I
    
    860
    -  say it's OK to have an unbound coercion binder in a RULE
    
    861
    -  provided its type is (c :: t~t).  Then, when the RULE
    
    862
    -  fires we can substitute <t> for c.
    
    860
    +  It's tricky to be sure this never happens, so instead I say it's OK
    
    861
    +  to have an unbound coercion binder in a RULE provided its type is (c
    
    862
    +  :: t~t).  Then, when the RULE fires we can substitute <t> for c.
    
    863 863
     
    
    864
    -  This actually happened (in a RULE for a local function)
    
    865
    -  in #13410, and also in test T10602.
    
    864
    +  This actually happened (in a RULE for a local function) in #13410,
    
    865
    +  and also in test T10602.
    
    866 866
     
    
    867 867
     Note [Cloning the template binders]
    
    868 868
     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    

  • compiler/GHC/Driver/Config.hs
    1 1
     -- | Subsystem configuration
    
    2 2
     module GHC.Driver.Config
    
    3
    -   ( initOptCoercionOpts
    
    4
    -   , initSimpleOpts
    
    3
    +   ( initSimpleOpts
    
    5 4
        , initEvalOpts
    
    6 5
        , EvalStep(..)
    
    7 6
        )
    
    ... ... @@ -11,15 +10,8 @@ import GHC.Prelude
    11 10
     
    
    12 11
     import GHC.Driver.DynFlags
    
    13 12
     import GHC.Core.SimpleOpt
    
    14
    -import GHC.Core.Coercion.Opt
    
    15 13
     import GHCi.Message (EvalOpts(..))
    
    16 14
     
    
    17
    --- | Initialise coercion optimiser configuration from DynFlags
    
    18
    -initOptCoercionOpts :: DynFlags -> OptCoercionOpts
    
    19
    -initOptCoercionOpts dflags = OptCoercionOpts
    
    20
    -   { optCoercionEnabled = gopt Opt_OptCoercion dflags
    
    21
    -   }
    
    22
    -
    
    23 15
     -- | Initialise Simple optimiser configuration from DynFlags
    
    24 16
     initSimpleOpts :: DynFlags -> SimpleOpts
    
    25 17
     initSimpleOpts dflags = SimpleOpts
    

  • compiler/GHC/Driver/Config/Core/Opt/Simplify.hs
    ... ... @@ -13,7 +13,6 @@ import GHC.Core.Opt.Simplify ( SimplifyExprOpts(..), SimplifyOpts(..) )
    13 13
     import GHC.Core.Opt.Simplify.Env ( FloatEnable(..), SimplMode(..), SimplPhase(..) )
    
    14 14
     import GHC.Core.Opt.Simplify.Monad ( TopEnvConfig(..) )
    
    15 15
     
    
    16
    -import GHC.Driver.Config ( initOptCoercionOpts )
    
    17 16
     import GHC.Driver.Config.Core.Lint ( initLintPassResultConfig )
    
    18 17
     import GHC.Driver.Config.Core.Rules ( initRuleOpts )
    
    19 18
     import GHC.Driver.Config.Core.Opt.Arity ( initArityOpts )
    
    ... ... @@ -73,7 +72,6 @@ initSimplMode dflags phase name = SimplMode
    73 72
       , sm_rule_opts = initRuleOpts dflags
    
    74 73
       , sm_case_folding = gopt Opt_CaseFolding dflags
    
    75 74
       , sm_case_merge = gopt Opt_CaseMerge dflags
    
    76
    -  , sm_co_opt_opts = initOptCoercionOpts dflags
    
    77 75
       }
    
    78 76
     
    
    79 77
     initGentleSimplMode :: DynFlags -> SimplMode
    

  • compiler/GHC/Driver/DynFlags.hs
    ... ... @@ -6,7 +6,7 @@ module GHC.Driver.DynFlags (
    6 6
             Language(..),
    
    7 7
             FatalMessager, FlushOut(..),
    
    8 8
             ProfAuto(..),
    
    9
    -        hasPprDebug, hasNoDebugOutput, hasNoStateHack, hasNoOptCoercion,
    
    9
    +        hasPprDebug, hasNoDebugOutput, hasNoStateHack,
    
    10 10
             dopt, dopt_set, dopt_unset,
    
    11 11
             gopt, gopt_set, gopt_unset,
    
    12 12
             wopt, wopt_set, wopt_unset,
    
    ... ... @@ -994,9 +994,6 @@ hasNoDebugOutput = dopt Opt_D_no_debug_output
    994 994
     hasNoStateHack :: DynFlags -> Bool
    
    995 995
     hasNoStateHack = gopt Opt_G_NoStateHack
    
    996 996
     
    
    997
    -hasNoOptCoercion :: DynFlags -> Bool
    
    998
    -hasNoOptCoercion flags = not (gopt Opt_OptCoercion flags)
    
    999
    -
    
    1000 997
     -- | Test whether a 'DumpFlag' is set
    
    1001 998
     dopt :: DumpFlag -> DynFlags -> Bool
    
    1002 999
     dopt = getDumpFlagFrom verbosity dumpFlags
    

  • compiler/GHC/Driver/Session.hs
    ... ... @@ -22,7 +22,7 @@ module GHC.Driver.Session (
    22 22
             FatalMessager, FlushOut(..),
    
    23 23
             ProfAuto(..),
    
    24 24
             glasgowExtsFlags,
    
    25
    -        hasPprDebug, hasNoDebugOutput, hasNoStateHack, hasNoOptCoercion,
    
    25
    +        hasPprDebug, hasNoDebugOutput, hasNoStateHack,
    
    26 26
             dopt, dopt_set, dopt_unset,
    
    27 27
             gopt, gopt_set, gopt_unset, setGeneralFlag', unSetGeneralFlag',
    
    28 28
             wopt, wopt_set, wopt_unset,
    

  • testsuite/tests/count-deps/CountDepsAst.stdout
    ... ... @@ -14,7 +14,6 @@ GHC.Core
    14 14
     GHC.Core.Class
    
    15 15
     GHC.Core.Coercion
    
    16 16
     GHC.Core.Coercion.Axiom
    
    17
    -GHC.Core.Coercion.Opt
    
    18 17
     GHC.Core.ConLike
    
    19 18
     GHC.Core.DataCon
    
    20 19
     GHC.Core.FVs
    

  • testsuite/tests/count-deps/CountDepsParser.stdout
    ... ... @@ -14,7 +14,6 @@ GHC.Core
    14 14
     GHC.Core.Class
    
    15 15
     GHC.Core.Coercion
    
    16 16
     GHC.Core.Coercion.Axiom
    
    17
    -GHC.Core.Coercion.Opt
    
    18 17
     GHC.Core.ConLike
    
    19 18
     GHC.Core.DataCon
    
    20 19
     GHC.Core.FVs
    

  • testsuite/tests/simplCore/should_compile/T8331.stderr
    ... ... @@ -20,9 +20,9 @@
    20 20
           = ($fApplicativeReaderT6 @s @r)
    
    21 21
             `cast` (forall (a ::~ <*>_N) (b ::~ <*>_N).
    
    22 22
                     <a>_R
    
    23
    -                ->_R <ReaderT r (ST s) b>_R
    
    24
    -                ->_R <r>_R ->_R Sym (N:ST <s>_N <a>_R)
    
    25
    -                     ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <a>_N)
    
    23
    +                ->_R <ReaderT r (ST s) b>_R ->_R <r>_R ->_R Sym (N:ST <s>_N <a>_R)
    
    24
    +                     ; (<ReaderT r (ST s) b>_R
    
    25
    +                        ->_R Sym (N:ReaderT <*>_N <r>_R <ST s>_R <a>_N))
    
    26 26
                     :: Coercible
    
    27 27
                          (forall a b. a -> ReaderT r (ST s) b -> r -> STRep s a)
    
    28 28
                          (forall a b. a -> ReaderT r (ST s) b -> ReaderT r (ST s) a))
    
    ... ... @@ -32,9 +32,9 @@
    32 32
           = ($fApplicativeReaderT1 @s @r)
    
    33 33
             `cast` (forall (a ::~ <*>_N) (b ::~ <*>_N).
    
    34 34
                     <ReaderT r (ST s) a>_R
    
    35
    -                ->_R <ReaderT r (ST s) b>_R
    
    36
    -                ->_R <r>_R ->_R Sym (N:ST <s>_N <a>_R)
    
    37
    -                     ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <a>_N)
    
    35
    +                ->_R <ReaderT r (ST s) b>_R ->_R <r>_R ->_R Sym (N:ST <s>_N <a>_R)
    
    36
    +                     ; (<ReaderT r (ST s) b>_R
    
    37
    +                        ->_R Sym (N:ReaderT <*>_N <r>_R <ST s>_R <a>_N))
    
    38 38
                     :: Coercible
    
    39 39
                          (forall a b.
    
    40 40
                           ReaderT r (ST s) a -> ReaderT r (ST s) b -> r -> STRep s a)
    
    ... ... @@ -78,9 +78,9 @@
    78 78
           = ($fApplicativeReaderT7 @s @r)
    
    79 79
             `cast` (forall (a ::~ <*>_N) (b ::~ <*>_N).
    
    80 80
                     <a -> b>_R
    
    81
    -                ->_R <ReaderT r (ST s) a>_R
    
    82
    -                ->_R <r>_R ->_R Sym (N:ST <s>_N <b>_R)
    
    83
    -                     ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <b>_N)
    
    81
    +                ->_R <ReaderT r (ST s) a>_R ->_R <r>_R ->_R Sym (N:ST <s>_N <b>_R)
    
    82
    +                     ; (<ReaderT r (ST s) a>_R
    
    83
    +                        ->_R Sym (N:ReaderT <*>_N <r>_R <ST s>_R <b>_N))
    
    84 84
                     :: Coercible
    
    85 85
                          (forall a b. (a -> b) -> ReaderT r (ST s) a -> r -> STRep s b)
    
    86 86
                          (forall a b. (a -> b) -> ReaderT r (ST s) a -> ReaderT r (ST s) b))
    
    ... ... @@ -91,9 +91,9 @@
    91 91
             `cast` (forall (a ::~ <*>_N) (b ::~ <*>_N) (c ::~ <*>_N).
    
    92 92
                     <a -> b -> c>_R
    
    93 93
                     ->_R <ReaderT r (ST s) a>_R
    
    94
    -                ->_R <ReaderT r (ST s) b>_R
    
    95
    -                ->_R <r>_R ->_R Sym (N:ST <s>_N <c>_R)
    
    96
    -                     ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <c>_N)
    
    94
    +                ->_R <ReaderT r (ST s) b>_R ->_R <r>_R ->_R Sym (N:ST <s>_N <c>_R)
    
    95
    +                     ; (<ReaderT r (ST s) b>_R
    
    96
    +                        ->_R Sym (N:ReaderT <*>_N <r>_R <ST s>_R <c>_N))
    
    97 97
                     :: Coercible
    
    98 98
                          (forall a b c.
    
    99 99
                           (a -> b -> c)
    
    ... ... @@ -114,9 +114,9 @@
    114 114
           $fApplicativeReaderT_$cpure @(ST s) @r $dApplicative
    
    115 115
           = ($fApplicativeReaderT5 @s @r)
    
    116 116
             `cast` (forall (a ::~ <*>_N).
    
    117
    -                <a>_R
    
    118
    -                ->_R <r>_R ->_R Sym (N:ST <s>_N <a>_R)
    
    119
    -                     ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <a>_N)
    
    117
    +                Sym (<a>_R
    
    118
    +                     ->_R N:ReaderT <*>_N <r>_R <ST s>_R <a>_N
    
    119
    +                          ; (<r>_R ->_R N:ST <s>_N <a>_R))
    
    120 120
                     :: Coercible
    
    121 121
                          (forall a. a -> r -> STRep s a)
    
    122 122
                          (forall a. a -> ReaderT r (ST s) a))
    
    ... ... @@ -125,9 +125,9 @@
    125 125
           $fMonadReaderT_$creturn @(ST s) @r $dMonad
    
    126 126
           = ($fApplicativeReaderT5 @s @r)
    
    127 127
             `cast` (forall (a ::~ <*>_N).
    
    128
    -                <a>_R
    
    129
    -                ->_R <r>_R ->_R Sym (N:ST <s>_N <a>_R)
    
    130
    -                     ; Sym (N:ReaderT <*>_N <r>_R <ST s>_R <a>_N)
    
    128
    +                Sym (<a>_R
    
    129
    +                     ->_R N:ReaderT <*>_N <r>_R <ST s>_R <a>_N
    
    130
    +                          ; (<r>_R ->_R N:ST <s>_N <a>_R))
    
    131 131
                     :: Coercible
    
    132 132
                          (forall a. a -> r -> STRep s a)
    
    133 133
                          (forall a. a -> ReaderT r (ST s) a))
    
    ... ... @@ -148,9 +148,9 @@
    148 148
                ($dMonadAbstractIOST :: MonadAbstractIOST (ReaderT Int (ST s))).
    
    149 149
           useAbstractMonad @(ReaderT Int (ST s)) $dMonadAbstractIOST
    
    150 150
           = (useAbstractMonad1 @s)
    
    151
    -        `cast` (<Int>_R
    
    152
    -                ->_R <Int>_R ->_R Sym (N:ST <s>_N <Int>_R)
    
    153
    -                     ; Sym (N:ReaderT <*>_N <Int>_R <ST s>_R <Int>_N)
    
    151
    +        `cast` (Sym (<Int>_R
    
    152
    +                     ->_R N:ReaderT <*>_N <Int>_R <ST s>_R <Int>_N
    
    153
    +                          ; (<Int>_R ->_R N:ST <s>_N <Int>_R))
    
    154 154
                     :: Coercible
    
    155 155
                          (Int -> Int -> STRep s Int) (Int -> ReaderT Int (ST s) Int))
    
    156 156