[Git][ghc/ghc][wip/issue-23832] Apply 6 suggestion(s) to 5 file(s)

Gergő Érdi (@cactus) gitlab at gitlab.haskell.org
Wed Aug 30 01:38:41 UTC 2023



Gergő Érdi pushed to branch wip/issue-23832 at Glasgow Haskell Compiler / GHC


Commits:
f7fad6da by sheaf at 2023-08-30T01:38:37+00:00
Apply 6 suggestion(s) to 5 file(s)
- - - - -


5 changed files:

- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Solver.hs
- docs/users_guide/9.10.1-notes.rst
- docs/users_guide/extending_ghc.rst


Changes:

=====================================
compiler/GHC/Tc/Errors/Ppr.hs
=====================================
@@ -1861,13 +1861,20 @@ instance Diagnostic TcRnMessage where
     TcRnInvalidDefaultedTyVar wanteds proposal bad_tvs ->
       mkSimpleDecorated $
       pprWithExplicitKindsWhen True $
-      vcat [ hang (text "Defaulting plugin returned invalid defaulting proposal when passed these constraints:") 2 $
-               pprQuotedList (map ctPred wanteds)
-           , hang (text "Defaulting proposal:") 2 $
-               ppr proposal
-           , hang (text "Of which the following are not an unfilled metavariables:") 2 $
-               pprQuotedList bad_tvs
+      vcat [ text "Invalid defaulting proposal."
+           , hang (text "The following type variable" <> plural bad_tvs <+> text "cannot be defaulted, as" <+> why <> colon)
+                2 (pprQuotedList bad_tvs)
+           , hang (text "Defaulting proposal:")
+                2 (ppr proposal)
+           , hang (text "Wanted constraints:")
+                2 (pprQuotedList (map ctPred wanteds))
            ]
+        where
+          why
+            | [_] <- bad_tvs
+            = text "it is not an unfilled metavariable"
+            | otherwise
+            = text "they are not unfilled metavariables"
 
   diagnosticReason = \case
     TcRnUnknownMessage m


=====================================
compiler/GHC/Tc/Errors/Types.hs
=====================================
@@ -4127,8 +4127,8 @@ data TcRnMessage where
   -}
   TcRnInvalidDefaultedTyVar
       :: ![Ct]              -- ^ The constraints passed to the plugin
-      -> [(TcTyVar, Type)]  -- ^ The plugin-proposed type variable defauilting
-      -> [TcTyVar]          -- ^ The invalid type variables of the proposal
+      -> [(TcTyVar, Type)]  -- ^ The plugin-proposed type variable defaults
+      -> NonEmpty TcTyVar   -- ^ The invalid type variables of the proposal
       -> TcRnMessage
 
   deriving Generic


=====================================
compiler/GHC/Tc/Solver.hs
=====================================
@@ -3708,8 +3708,6 @@ disambigMultiGroup orig_wanteds wanteds = anyM propose
   where
     propose proposal
         = do { traceTcS "disambigMultiGroup {" (vcat [ ppr proposal, ppr wanteds ])
-             -- Only with a defaulting plugin could these lengths be mismatched.
-             -- We report an error, instead of silently failing to default.
              ; invalid_tvs <- filterOutM TcS.isUnfilledMetaTyVar tvs
              ; unless (null invalid_tvs) $
                  errInvalidDefaultedTyVar orig_wanteds proposal invalid_tvs
@@ -3724,7 +3722,7 @@ disambigMultiGroup orig_wanteds wanteds = anyM propose
                           ; wrapWarnTcS $ mapM_ (uncurry $ warnDefaulting wanteds) proposal
                           ; traceTcS "disambigMultiGroup succeeded }" (ppr proposal)
                           ; return True }
-                   Nothing -> -- Failure: try with the next type
+                   Nothing -> -- Failure: try with the next defaulting group
                        do { traceTcS "disambigMultiGroup failed, will try other default types }"
                                (ppr proposal)
                           ; return False } }


=====================================
docs/users_guide/9.10.1-notes.rst
=====================================
@@ -52,7 +52,7 @@ Compiler
   suppress printing timings to the console. See :ghc-ticket:`20316`.
 
 - Defaulting plugins can now propose solutions to entangled sets of type variables. This allows defaulting
-  of multi-parameter type classes. See :ghc-tickect:`23832`.
+  of multi-parameter type classes. See :ghc-ticket:`23832`.
 
 GHCi
 ~~~~


=====================================
docs/users_guide/extending_ghc.rst
=====================================
@@ -1360,16 +1360,11 @@ Defaulting plugins have a single access point in the `GHC.Tc.Types` module
     -- | A collection of candidate default types for sets of type variables.
     data DefaultingProposal
       = DefaultingProposal
-        { deProposalTyVars :: [TcTyVar]
-          -- ^ The type variables to default.
-        , deProposalCandidates :: [[Type]]
-          -- ^ Candidate types to default the type variables to.
-          --
-          -- All of the inner lists should have the same length as the
-          -- list of type variables we are defaulting.
+        { deProposals :: [[(TcTyVar, Type)]]
+          -- ^ The type variable assignments to try.
         , deProposalCts :: [Ct]
           -- ^ The constraints against which defaults are checked.
-        }
+      }
 
     type FillDefaulting = WantedConstraints -> TcPluginM [DefaultingProposal]
 



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f7fad6da7356b33a0fc6465e8b04ceacae434eb4
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/20230829/9e37fae2/attachment-0001.html>


More information about the ghc-commits mailing list