[Git][ghc/ghc][master] Update commentary and slightly refactor GHC.Tc.Deriv.Infer

Marge Bot gitlab at gitlab.haskell.org
Thu Apr 23 03:16:22 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
c409961a by Ryan Scott at 2020-04-22T23:16:12-04:00
Update commentary and slightly refactor GHC.Tc.Deriv.Infer

There was some out-of-date commentary in `GHC.Tc.Deriv.Infer` that
has been modernized. Along the way, I removed the `bad` constraints
in `simplifyDeriv`, which did not serve any useful purpose (besides
being printed in debugging output).

Fixes #18073.

- - - - -


1 changed file:

- compiler/GHC/Tc/Deriv/Infer.hs


Changes:

=====================================
compiler/GHC/Tc/Deriv/Infer.hs
=====================================
@@ -803,28 +803,31 @@ simplifyDeriv pred tvs thetas
        ; solved_wanteds <- zonkWC solved_wanteds
 
        -- See [STEP DAC HOIST]
-       -- Split the resulting constraints into bad and good constraints,
-       -- building an @unsolved :: WantedConstraints@ representing all
-       -- the constraints we can't just shunt to the predicates.
-       -- See Note [Exotic derived instance contexts]
+       -- From the simplified constraints extract a subset 'good' that will
+       -- become the context 'min_theta' for the derived instance.
        ; let residual_simple = approximateWC True solved_wanteds
-             (bad, good) = partitionBagWith get_good residual_simple
-
-             get_good :: Ct -> Either Ct PredType
+             good = mapMaybeBag get_good residual_simple
+
+             -- Returns @Just p@ (where @p@ is the type of the Ct) if a Ct is
+             -- suitable to be inferred in the context of a derived instance.
+             -- Returns @Nothing@ if the Ct is too exotic.
+             -- See Note [Exotic derived instance contexts] for what
+             -- constitutes an exotic constraint.
+             get_good :: Ct -> Maybe PredType
              get_good ct | validDerivPred skol_set p
                          , isWantedCt ct
-                         = Right p
+                         = Just p
                           -- TODO: This is wrong
                           -- NB re 'isWantedCt': residual_wanted may contain
                           -- unsolved CtDerived and we stick them into the
                           -- bad set so that reportUnsolved may decide what
                           -- to do with them
                          | otherwise
-                         = Left ct
+                         = Nothing
                            where p = ctPred ct
 
        ; traceTc "simplifyDeriv outputs" $
-         vcat [ ppr tvs_skols, ppr residual_simple, ppr good, ppr bad ]
+         vcat [ ppr tvs_skols, ppr residual_simple, ppr good ]
 
        -- Return the good unsolved constraints (unskolemizing on the way out.)
        ; let min_theta = mkMinimalBySCs id (bagToList good)
@@ -838,6 +841,10 @@ simplifyDeriv pred tvs thetas
                           -- The reverse substitution (sigh)
 
        -- See [STEP DAC RESIDUAL]
+       -- Ensure that min_theta is enough to solve /all/ the constraints in
+       -- solved_wanteds, by solving the implication constraint
+       --
+       --    forall tvs. min_theta => solved_wanteds
        ; min_theta_vars <- mapM newEvVar min_theta
        ; (leftover_implic, _)
            <- buildImplicationFor tc_lvl skol_info tvs_skols



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c409961aea59d2fe2ae71036a1ae6d94c4ee05c8

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c409961aea59d2fe2ae71036a1ae6d94c4ee05c8
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200422/05a18208/attachment-0001.html>


More information about the ghc-commits mailing list