Simon Peyton Jones pushed to branch wip/T23162-spj at Glasgow Haskell Compiler / GHC

Commits:

3 changed files:

Changes:

  • compiler/GHC/Tc/Solver/Equality.hs
    ... ... @@ -554,24 +554,21 @@ can_eq_nc_forall ev eq_rel s1 s2
    554 554
                        ; traceTcS "Trying to solve the implication" (ppr s1 $$ ppr s2 $$ ppr wanteds)
    
    555 555
     
    
    556 556
                        -- Solve the `wanteds` in a nested context
    
    557
    -                   ; ev_binds_var <- newNoTcEvBinds
    
    557
    +                   -- Use the /same/ TcEvBinds var as the context; we do not expect any dict binds
    
    558
    +                   -- but we do want to record any used Given coercions (in `evb_tcvs`) so that
    
    559
    +                   -- they are kept alive by `neededEvVars`. Admittedly they are free in `all_co`,
    
    560
    +                   -- but only if we zonk it, which `neededEvVars` does not do (see test T7196).
    
    561
    +                   ; ev_binds_var <- getTcEvBindsVar
    
    558 562
                        ; residual_wanted <- nestImplicTcS skol_info_anon ev_binds_var tclvl $
    
    559 563
                                             solveSimpleWanteds wanteds
    
    560 564
     
    
    561 565
                        ; return (all_co, isSolvedWC residual_wanted) }
    
    562 566
     
    
    563
    -
    
    564 567
           -- Kick out any inerts constraints that mention unified type variables
    
    565 568
           ; kickOutAfterUnification unifs
    
    566 569
     
    
    567 570
           ; if solved
    
    568
    -        then do { all_co <- zonkCo all_co
    
    569
    -                     -- setWantedEq will add `all_co` to the `ebv_tcvs`, to record
    
    570
    -                     -- that `all_co` is used.  But if `all_co` contains filled
    
    571
    -                     -- CoercionHoles, from the nested solve, and we may miss the
    
    572
    -                     -- use of CoVars.  Test T7196 showed this up
    
    573
    -
    
    574
    -                ; setWantedEq orig_dest emptyCoHoleSet all_co
    
    571
    +        then do { setWantedEq orig_dest emptyCoHoleSet all_co
    
    575 572
                          -- emptyCoHoleSet: fully solved, so all_co has no holes
    
    576 573
                     ; stopWith ev "Polytype equality: solved" }
    
    577 574
     
    

  • compiler/GHC/Tc/Types/Constraint.hs
    ... ... @@ -2568,42 +2568,41 @@ Note [Wanteds rewrite Wanteds]
    2568 2568
     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    2569 2569
     Should one Wanted constraint be allowed to rewrite another?
    
    2570 2570
     
    
    2571
    -This example (along with #8450) suggests not:
    
    2572
    -   f :: a -> Bool
    
    2573
    -   f x = ( [x,'c'], [x,True] ) `seq` True
    
    2574
    -Here we get
    
    2575
    -  [W] a ~ Char
    
    2576
    -  [W] a ~ Bool
    
    2577
    -but we do not want to complain about Bool ~ Char!
    
    2578
    -
    
    2579
    -This example suggests yes (indexed-types/should_fail/T4093a):
    
    2580
    -  type family Foo a
    
    2581
    -  f :: (Foo e ~ Maybe e) => Foo e
    
    2582
    -In the ambiguity check, we get
    
    2583
    -  [G] g1 :: Foo e ~ Maybe e
    
    2584
    -  [W] w1 :: Foo alpha ~ Foo e
    
    2585
    -  [W] w2 :: Foo alpha ~ Maybe alpha
    
    2586
    -w1 gets rewritten by the Given to become
    
    2587
    -  [W] w3 :: Foo alpha ~ Maybe e
    
    2588
    -Now, the only way to make progress is to allow Wanteds to rewrite Wanteds.
    
    2589
    -Rewriting w3 with w2 gives us
    
    2590
    -  [W] w4 :: Maybe alpha ~ Maybe e
    
    2591
    -which will soon get us to alpha := e and thence to victory.
    
    2592
    -
    
    2593
    -TL;DR we want equality saturation.
    
    2571
    +This example (along with #8450) suggests "no":
    
    2572
    +       f :: a -> Bool
    
    2573
    +       f x = ( [x,'c'], [x,True] ) `seq` True
    
    2574
    +    Here we get
    
    2575
    +      [W] a ~ Char
    
    2576
    +      [W] a ~ Bool
    
    2577
    +    but we do not want to complain about Bool ~ Char!
    
    2578
    +
    
    2579
    +This example suggests "yes" (indexed-types/should_fail/T4093a):
    
    2580
    +      type family Foo a
    
    2581
    +      f :: (Foo e ~ Maybe e) => Foo e
    
    2582
    +    In the ambiguity check, we get
    
    2583
    +      [G] g1 :: Foo e ~ Maybe e
    
    2584
    +      [W] w1 :: Foo alpha ~ Foo e
    
    2585
    +      [W] w2 :: Foo alpha ~ Maybe alpha
    
    2586
    +    w1 gets rewritten by the Given to become
    
    2587
    +      [W] w3 :: Foo alpha ~ Maybe e
    
    2588
    +    Now, the only way to make progress is to allow Wanteds to rewrite Wanteds.
    
    2589
    +    Rewriting w3 with w2 gives us
    
    2590
    +      [W] w4 :: Maybe alpha ~ Maybe e
    
    2591
    +    which will soon get us to alpha := e and thence to victory.
    
    2592
    +    TL;DR we want equality saturation.
    
    2594 2593
     
    
    2595 2594
     We thus want Wanteds to rewrite Wanteds in order to accept more programs,
    
    2596 2595
     but we don't want Wanteds to rewrite Wanteds because doing so can create
    
    2597 2596
     inscrutable error messages. To solve this dilemma:
    
    2598 2597
     
    
    2599
    -(WRW1) The rewriters of a Wanted.  We do allow Wanteds to rewrite Wanteds, but each
    
    2600
    -  unsolved Wanted tracks
    
    2598
    +(WRW1) ctev_rewriters: the rewriters of a Wanted.  We /do/ allow Wanteds to
    
    2599
    +  rewrite Wanteds, but each unsolved Wanted tracks
    
    2601 2600
          the set of Wanteds that it has been rewritten by
    
    2602 2601
       in its CoHoleSet, stored in the `ctev_rewriters` field of the CtWanted
    
    2603 2602
       constructor of CtEvidence.  (Only Wanteds have CoHoleSets.)
    
    2604 2603
     
    
    2605
    -  If the rewriter set is empty, then the constaint has been not been rewritten
    
    2606
    -  by any unsolved constraint.
    
    2604
    +  Key point: if the rewriter set is empty, then the constaint has been not been
    
    2605
    +  rewritten by any unsolved constraint.
    
    2607 2606
     
    
    2608 2607
     (WRW2) A CoHoleSet is just a set of CoercionHoles. This is sufficient because only
    
    2609 2608
       equalities (evidenced by coercion holes) are used for rewriting; other
    

  • compiler/GHC/Tc/Types/Evidence.hs
    ... ... @@ -392,6 +392,8 @@ data EvBindsVar
    392 392
           --  so that we can report unused given constraints,
    
    393 393
           --  in GHC.Tc.Solver.neededEvVars
    
    394 394
           -- See Note [Tracking redundant constraints] in GHC.Tc.Solver
    
    395
    +      -- Also: we garbage-collect unused bindings in `neededEvVars`,
    
    396
    +      --       so this matters for correctness too.
    
    395 397
         }
    
    396 398
     
    
    397 399
       | CoEvBindsVar {  -- See Note [Coercion evidence only]