[Git][ghc/ghc][wip/andreask/spec_tyfams] Another subtle wibble: (ID8)

Simon Peyton Jones pushed to branch wip/andreask/spec_tyfams at Glasgow Haskell Compiler / GHC Commits: dc677e8d by Simon Peyton Jones at 2025-04-28T10:57:34+01:00 Another subtle wibble: (ID8) - - - - - 1 changed file: - compiler/GHC/Core/Opt/Specialise.hs Changes: ===================================== compiler/GHC/Core/Opt/Specialise.hs ===================================== @@ -3148,7 +3148,7 @@ because the code for the specialised f is not improved at all, because d is lambda-bound. We simply get junk specialisations. What is "interesting"? Our Main Plan is to use `exprIsConApp_maybe` to see -if the argumeng is a dictionary constructor applied to some arguments, in which +if the argument is a dictionary constructor applied to some arguments, in which case we can clearly specialise. But there are wrinkles: (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: in point is constraint tuples (% d1, .., dn %); a constraint N-tuple is a class with N superclasses and no methods. -(ID7) A unary (single-method) class is currently represented by (meth |> co). - We will unwrap the cast (see (ID5)) and then want to reply "yes" if the method - has any struture. We use `exprIsHNF` for this. (We plan a new story for unary - classes, see #23109, and this special case will become irrelevant.) +(ID7) A unary (single-method) class is currently represented by (meth |> co). We + will unwrap the cast (see (ID5)) and then want to reply "yes" if the method + has any struture. We rather arbitrarily use `exprIsHNF` for this. (We plan a + new story for unary classes, see #23109, and this special case will become + irrelevant.) + +(ID8) Sadly, if `exprIsConApp_maybe` says Nothing, we still want to treat a + non-trivial argument as interesting. In T19695 we have this: + askParams :: Monad m => blah + mhelper :: MonadIO m => blah + mhelper (d:MonadIO m) = ...(askParams @m ($p1 d)).... + where `$p1` is the superclass selector for `MonadIO`. Now, if `mhelper` is + specialised at `Handler` we'll get this call in the specialised `$smhelper`: + askParams @Handler ($p1 $fMonadIOHandler) + and we /definitely/ want to specialise that, even though the argument isn't + visibly a dictionary application. In fact the specialiser fires the superclass + selector rule (see Note [Fire rules in the specialiser]), so we get + askParams @Handler ($cp1MonadIO $fMonadIOIO) + but it /still/ doesn't look like a dictionary application. + + Conclusion: we optimistically assume that any non-trivial argument is worth + specialising on. + + So why do the `exprIsConApp_maybe` and `Cast` stuff? Because we want to look + under type-family casts (ID1) and constraint tuples (ID6). Note [Update unfolding after specialisation] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -3256,20 +3277,13 @@ interestingDict env (Var v) -- See (ID3) and (ID5) = interestingDict env rhs interestingDict env arg -- Main Plan: use exprIsConApp_maybe - | Just (_, _, data_con, _tys, args) <- exprIsConApp_maybe in_scope_env arg - , Just cls <- tyConClass_maybe (dataConTyCon data_con) - , (not . couldBeIPLike) arg_ty -- See (ID4) - = if null (classMethods cls) -- See (ID6) - then any (interestingDict env) args - else True - | Cast inner_arg _ <- arg -- See (ID5) = if | isConstraintKind $ typeKind $ exprType inner_arg -- If coercions were always homo-kinded, we'd know -- that this would be the only case -> interestingDict env inner_arg - -- Cheeck for an implicit parameter + -- Check for an implicit parameter at the top | Just (cls,_) <- getClassPredTys_maybe arg_ty , isIPClass cls -- See (ID4) -> False @@ -3278,10 +3292,18 @@ interestingDict env arg -- Main Plan: use exprIsConApp_maybe | otherwise -> exprIsHNF arg -- See (ID7) + | Just (_, _, data_con, _tys, args) <- exprIsConApp_maybe in_scope_env arg + , Just cls <- tyConClass_maybe (dataConTyCon data_con) + , not_ip_like -- See (ID4) + = if null (classMethods cls) -- See (ID6) + then any (interestingDict env) args + else True + | otherwise - = False + = not (exprIsTrivial arg) && not_ip_like -- See (ID8) where - arg_ty = exprType arg + arg_ty = exprType arg + not_ip_like = not (couldBeIPLike arg_ty) in_scope_env = ISE (substInScopeSet $ se_subst env) realIdUnfolding thenUDs :: UsageDetails -> UsageDetails -> UsageDetails View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dc677e8d65cec9787d22d5742bc14634... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dc677e8d65cec9787d22d5742bc14634... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Simon Peyton Jones (@simonpj)