Simon Peyton Jones pushed to branch wip/T26315 at Glasgow Haskell Compiler / GHC

Commits:

3 changed files:

Changes:

  • compiler/GHC/Tc/Types/Constraint.hs
    ... ... @@ -1772,7 +1772,8 @@ will be able to report a more informative error:
    1772 1772
     type ApproxWC = ( Bag Ct          -- Free quantifiable constraints
    
    1773 1773
                     , TcTyCoVarSet )  -- Free vars of non-quantifiable constraints
    
    1774 1774
                                       -- due to shape, or enclosing equality
    
    1775
    -
    
    1775
    +   -- Why do we need that TcTyCoVarSet of non-quantifiable constraints?
    
    1776
    +   -- See (DP1) in Note [decideAndPromoteTyVars] in GHC.Tc.Solver
    
    1776 1777
     approximateWC :: Bool -> WantedConstraints -> Bag Ct
    
    1777 1778
     approximateWC include_non_quantifiable cts
    
    1778 1779
       = fst (approximateWCX include_non_quantifiable cts)
    
    ... ... @@ -1840,7 +1841,8 @@ approximateWCX include_non_quantifiable wc
    1840 1841
     
    
    1841 1842
                IrredPred {}  -> True  -- See Wrinkle (W2)
    
    1842 1843
     
    
    1843
    -           ForAllPred {} -> False  -- Never quantify these
    
    1844
    +           ForAllPred {} -> warnPprTrace True "Unexpected ForAllPred" (ppr pred) $
    
    1845
    +                            False  -- See Wrinkle (W4)
    
    1844 1846
     
    
    1845 1847
         -- See Note [Quantifying over equality constraints]
    
    1846 1848
         quantify_equality NomEq  ty1 ty2 = quant_fun ty1 || quant_fun ty2
    
    ... ... @@ -1904,6 +1906,21 @@ Wrinkle (W3)
    1904 1906
       we /do/ want to float out of equalities (#12797).  Hence we just union the two
    
    1905 1907
       returned lists.
    
    1906 1908
     
    
    1909
    +Wrinkle (W4)
    
    1910
    +  In #26376 we had constraints
    
    1911
    +    [W] d1 : Functor f[tau:1]
    
    1912
    +    [W] d2 : Functor p[tau:1]
    
    1913
    +    [W] d3 : forall a. Functor (p[tau:1]) a   -- A quantified constraint
    
    1914
    +  We certainly don't want to /quantify/ over d3; but we /do/ want to
    
    1915
    +  quantify over `p`, so it would be a mistake to make the function monomorphic
    
    1916
    +  in `p` just because `p` is mentioned in this quantified constraint.
    
    1917
    +
    
    1918
    +  Happily this problem cannot happen any more.  That quantified constraint `d3`
    
    1919
    +  dates from a time when we flirted with an all-or-nothing strategy for
    
    1920
    +  quantified constraints Nowadays we'll never see this: we'll have simplified
    
    1921
    +  that quantified constraint into a implication constraint.  (Exception:
    
    1922
    +  SPECIALISE pragmas: see (WFA4) in Note [Solving a Wanted forall-constraint].
    
    1923
    +  But there we don't use approximateWC.)
    
    1907 1924
     
    
    1908 1925
     ------ Historical note -----------
    
    1909 1926
     There used to be a second caveat, driven by #8155
    

  • testsuite/tests/typecheck/should_compile/T26376.hs
    1
    +module T26376 where
    
    2
    +
    
    3
    +import Data.Bifunctor (first)
    
    4
    +
    
    5
    +works x y = first (const x) <$> y
    
    6
    +
    
    7
    +main :: IO ()
    
    8
    +main = do
    
    9
    +  let fails x y = first (const x) <$> y
    
    10
    +  return ()

  • testsuite/tests/typecheck/should_compile/all.T
    ... ... @@ -949,4 +949,5 @@ test('T25992a', normal, compile, [''])
    949 949
     test('T26346', normal, compile, [''])
    
    950 950
     test('T26358', expect_broken(26358), compile, [''])
    
    951 951
     test('T26345', normal, compile, [''])
    
    952
    +test('T26376', normal, compile, [''])
    
    952 953