Zubin pushed to branch wip/9.12.3-backports at Glasgow Haskell Compiler / GHC

Commits:

4 changed files:

Changes:

  • compiler/GHC/Tc/Gen/App.hs
    ... ... @@ -2040,6 +2040,10 @@ qlUnify ty1 ty2
    2040 2040
         go_flexi1 kappa ty2  -- ty2 is zonked
    
    2041 2041
           | -- See Note [QuickLook unification] (UQL1)
    
    2042 2042
             simpleUnifyCheck UC_QuickLook kappa ty2
    
    2043
    +      , checkTopShape (metaTyVarInfo kappa) ty2
    
    2044
    +          -- NB: don't forget to do a shape check, as we might be dealing
    
    2045
    +          -- with an ordinary metavariable (and not a quick-look instantiation variable).
    
    2046
    +          -- (Forgetting this led to #25950.)
    
    2043 2047
           = do { co <- unifyKind (Just (TypeThing ty2)) ty2_kind kappa_kind
    
    2044 2048
                        -- unifyKind: see (UQL2) in Note [QuickLook unification]
    
    2045 2049
                        --            and (MIV2) in Note [Monomorphise instantiation variables]
    

  • testsuite/tests/typecheck/should_fail/T25950.hs
    1
    +{-# LANGUAGE PartialTypeSignatures #-}
    
    2
    +
    
    3
    +module T25950 where
    
    4
    +
    
    5
    +fails :: _ => a
    
    6
    +fails = id $ ()

  • testsuite/tests/typecheck/should_fail/T25950.stderr
    1
    +T25950.hs:6:9: error: [GHC-25897]
    
    2
    +    • Couldn't match expected type ‘a’ with actual type ‘()’
    
    3
    +      ‘a’ is a rigid type variable bound by
    
    4
    +        the inferred type of fails :: a
    
    5
    +        at T25950.hs:5:1-15
    
    6
    +    • In the expression: id $ ()
    
    7
    +      In an equation for ‘fails’: fails = id $ ()
    
    8
    +    • Relevant bindings include fails :: a (bound at T25950.hs:6:1)
    
    9
    +

  • testsuite/tests/typecheck/should_fail/all.T
    ... ... @@ -724,6 +724,7 @@ test('T17594c', normal, compile_fail, [''])
    724 724
     test('T17594d', normal, compile_fail, [''])
    
    725 725
     test('T17594g', normal, compile_fail, [''])
    
    726 726
     
    
    727
    +test('T25950', normal, compile_fail, [''])
    
    727 728
     test('T24470a', normal, compile_fail, [''])
    
    728 729
     test('T24553', normal, compile_fail, [''])
    
    729 730
     test('T23739b', normal, compile_fail, [''])