... |
... |
@@ -3148,7 +3148,7 @@ because the code for the specialised f is not improved at all, because |
3148
|
3148
|
d is lambda-bound. We simply get junk specialisations.
|
3149
|
3149
|
|
3150
|
3150
|
What is "interesting"? Our Main Plan is to use `exprIsConApp_maybe` to see
|
3151
|
|
-if the argumeng is a dictionary constructor applied to some arguments, in which
|
|
3151
|
+if the argument is a dictionary constructor applied to some arguments, in which
|
3152
|
3152
|
case we can clearly specialise. But there are wrinkles:
|
3153
|
3153
|
|
3154
|
3154
|
(ID1) Note that we look at the argument /term/, not its /type/. Suppose the
|
... |
... |
@@ -3201,10 +3201,31 @@ case we can clearly specialise. But there are wrinkles: |
3201
|
3201
|
in point is constraint tuples (% d1, .., dn %); a constraint N-tuple is a class
|
3202
|
3202
|
with N superclasses and no methods.
|
3203
|
3203
|
|
3204
|
|
-(ID7) A unary (single-method) class is currently represented by (meth |> co).
|
3205
|
|
- We will unwrap the cast (see (ID5)) and then want to reply "yes" if the method
|
3206
|
|
- has any struture. We use `exprIsHNF` for this. (We plan a new story for unary
|
3207
|
|
- classes, see #23109, and this special case will become irrelevant.)
|
|
3204
|
+(ID7) A unary (single-method) class is currently represented by (meth |> co). We
|
|
3205
|
+ will unwrap the cast (see (ID5)) and then want to reply "yes" if the method
|
|
3206
|
+ has any struture. We rather arbitrarily use `exprIsHNF` for this. (We plan a
|
|
3207
|
+ new story for unary classes, see #23109, and this special case will become
|
|
3208
|
+ irrelevant.)
|
|
3209
|
+
|
|
3210
|
+(ID8) Sadly, if `exprIsConApp_maybe` says Nothing, we still want to treat a
|
|
3211
|
+ non-trivial argument as interesting. In T19695 we have this:
|
|
3212
|
+ askParams :: Monad m => blah
|
|
3213
|
+ mhelper :: MonadIO m => blah
|
|
3214
|
+ mhelper (d:MonadIO m) = ...(askParams @m ($p1 d))....
|
|
3215
|
+ where `$p1` is the superclass selector for `MonadIO`. Now, if `mhelper` is
|
|
3216
|
+ specialised at `Handler` we'll get this call in the specialised `$smhelper`:
|
|
3217
|
+ askParams @Handler ($p1 $fMonadIOHandler)
|
|
3218
|
+ and we /definitely/ want to specialise that, even though the argument isn't
|
|
3219
|
+ visibly a dictionary application. In fact the specialiser fires the superclass
|
|
3220
|
+ selector rule (see Note [Fire rules in the specialiser]), so we get
|
|
3221
|
+ askParams @Handler ($cp1MonadIO $fMonadIOIO)
|
|
3222
|
+ but it /still/ doesn't look like a dictionary application.
|
|
3223
|
+
|
|
3224
|
+ Conclusion: we optimistically assume that any non-trivial argument is worth
|
|
3225
|
+ specialising on.
|
|
3226
|
+
|
|
3227
|
+ So why do the `exprIsConApp_maybe` and `Cast` stuff? Because we want to look
|
|
3228
|
+ under type-family casts (ID1) and constraint tuples (ID6).
|
3208
|
3229
|
|
3209
|
3230
|
Note [Update unfolding after specialisation]
|
3210
|
3231
|
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
... |
... |
@@ -3256,20 +3277,13 @@ interestingDict env (Var v) -- See (ID3) and (ID5) |
3256
|
3277
|
= interestingDict env rhs
|
3257
|
3278
|
|
3258
|
3279
|
interestingDict env arg -- Main Plan: use exprIsConApp_maybe
|
3259
|
|
- | Just (_, _, data_con, _tys, args) <- exprIsConApp_maybe in_scope_env arg
|
3260
|
|
- , Just cls <- tyConClass_maybe (dataConTyCon data_con)
|
3261
|
|
- , (not . couldBeIPLike) arg_ty -- See (ID4)
|
3262
|
|
- = if null (classMethods cls) -- See (ID6)
|
3263
|
|
- then any (interestingDict env) args
|
3264
|
|
- else True
|
3265
|
|
-
|
3266
|
3280
|
| Cast inner_arg _ <- arg -- See (ID5)
|
3267
|
3281
|
= if | isConstraintKind $ typeKind $ exprType inner_arg
|
3268
|
3282
|
-- If coercions were always homo-kinded, we'd know
|
3269
|
3283
|
-- that this would be the only case
|
3270
|
3284
|
-> interestingDict env inner_arg
|
3271
|
3285
|
|
3272
|
|
- -- Cheeck for an implicit parameter
|
|
3286
|
+ -- Check for an implicit parameter at the top
|
3273
|
3287
|
| Just (cls,_) <- getClassPredTys_maybe arg_ty
|
3274
|
3288
|
, isIPClass cls -- See (ID4)
|
3275
|
3289
|
-> False
|
... |
... |
@@ -3278,10 +3292,18 @@ interestingDict env arg -- Main Plan: use exprIsConApp_maybe |
3278
|
3292
|
| otherwise
|
3279
|
3293
|
-> exprIsHNF arg -- See (ID7)
|
3280
|
3294
|
|
|
3295
|
+ | Just (_, _, data_con, _tys, args) <- exprIsConApp_maybe in_scope_env arg
|
|
3296
|
+ , Just cls <- tyConClass_maybe (dataConTyCon data_con)
|
|
3297
|
+ , not_ip_like -- See (ID4)
|
|
3298
|
+ = if null (classMethods cls) -- See (ID6)
|
|
3299
|
+ then any (interestingDict env) args
|
|
3300
|
+ else True
|
|
3301
|
+
|
3281
|
3302
|
| otherwise
|
3282
|
|
- = False
|
|
3303
|
+ = not (exprIsTrivial arg) && not_ip_like -- See (ID8)
|
3283
|
3304
|
where
|
3284
|
|
- arg_ty = exprType arg
|
|
3305
|
+ arg_ty = exprType arg
|
|
3306
|
+ not_ip_like = not (couldBeIPLike arg_ty)
|
3285
|
3307
|
in_scope_env = ISE (substInScopeSet $ se_subst env) realIdUnfolding
|
3286
|
3308
|
|
3287
|
3309
|
thenUDs :: UsageDetails -> UsageDetails -> UsageDetails
|