
Simon Peyton Jones pushed to branch wip/T26315 at Glasgow Haskell Compiler / GHC Commits: ec37aa59 by Simon Peyton Jones at 2025-09-02T17:22:24+01:00 Add test for #26376 - - - - - 3 changed files: - compiler/GHC/Tc/Types/Constraint.hs - + testsuite/tests/typecheck/should_compile/T26376.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== compiler/GHC/Tc/Types/Constraint.hs ===================================== @@ -1772,7 +1772,8 @@ will be able to report a more informative error: type ApproxWC = ( Bag Ct -- Free quantifiable constraints , TcTyCoVarSet ) -- Free vars of non-quantifiable constraints -- due to shape, or enclosing equality - + -- Why do we need that TcTyCoVarSet of non-quantifiable constraints? + -- See (DP1) in Note [decideAndPromoteTyVars] in GHC.Tc.Solver approximateWC :: Bool -> WantedConstraints -> Bag Ct approximateWC include_non_quantifiable cts = fst (approximateWCX include_non_quantifiable cts) @@ -1840,7 +1841,8 @@ approximateWCX include_non_quantifiable wc IrredPred {} -> True -- See Wrinkle (W2) - ForAllPred {} -> False -- Never quantify these + ForAllPred {} -> warnPprTrace True "Unexpected ForAllPred" (ppr pred) $ + False -- See Wrinkle (W4) -- See Note [Quantifying over equality constraints] quantify_equality NomEq ty1 ty2 = quant_fun ty1 || quant_fun ty2 @@ -1904,6 +1906,21 @@ Wrinkle (W3) we /do/ want to float out of equalities (#12797). Hence we just union the two returned lists. +Wrinkle (W4) + In #26376 we had constraints + [W] d1 : Functor f[tau:1] + [W] d2 : Functor p[tau:1] + [W] d3 : forall a. Functor (p[tau:1]) a -- A quantified constraint + We certainly don't want to /quantify/ over d3; but we /do/ want to + quantify over `p`, so it would be a mistake to make the function monomorphic + in `p` just because `p` is mentioned in this quantified constraint. + + Happily this problem cannot happen any more. That quantified constraint `d3` + dates from a time when we flirted with an all-or-nothing strategy for + quantified constraints Nowadays we'll never see this: we'll have simplified + that quantified constraint into a implication constraint. (Exception: + SPECIALISE pragmas: see (WFA4) in Note [Solving a Wanted forall-constraint]. + But there we don't use approximateWC.) ------ Historical note ----------- There used to be a second caveat, driven by #8155 ===================================== testsuite/tests/typecheck/should_compile/T26376.hs ===================================== @@ -0,0 +1,10 @@ +module T26376 where + +import Data.Bifunctor (first) + +works x y = first (const x) <$> y + +main :: IO () +main = do + let fails x y = first (const x) <$> y + return () ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -949,4 +949,5 @@ test('T25992a', normal, compile, ['']) test('T26346', normal, compile, ['']) test('T26358', expect_broken(26358), compile, ['']) test('T26345', normal, compile, ['']) +test('T26376', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ec37aa591ebe0f0dfce5842d4630ea23... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ec37aa591ebe0f0dfce5842d4630ea23... You're receiving this email because of your account on gitlab.haskell.org.