Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC
Commits:
-
d9e481ee
by Apoorv Ingle at 2025-12-01T18:25:06-06:00
7 changed files:
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Expr.hs
- testsuite/tests/default/default-fail05.stderr
- testsuite/tests/indexed-types/should_fail/T1897b.stderr
- testsuite/tests/typecheck/should_compile/T14590.stderr
- testsuite/tests/typecheck/should_fail/T6069.stderr
- testsuite/tests/typecheck/should_fail/T7857.stderr
Changes:
| ... | ... | @@ -679,10 +679,6 @@ quickLookKeys = [dollarIdKey, leftSectionKey, rightSectionKey] |
| 679 | 679 | * *
|
| 680 | 680 | ********************************************************************* -}
|
| 681 | 681 | |
| 682 | --- setQLInstLevel :: QLFlag -> TcM a -> TcM a
|
|
| 683 | --- setQLInstLevel DoQL thing_inside = setTcLevel QLInstVar thing_inside
|
|
| 684 | --- setQLInstLevel NoQL thing_inside = thing_inside
|
|
| 685 | - |
|
| 686 | 682 | tcInstFun :: QLFlag
|
| 687 | 683 | -> Bool -- False <=> Instantiate only /top-level, inferred/ variables;
|
| 688 | 684 | -- so may return a sigma-type
|
| ... | ... | @@ -706,9 +702,7 @@ tcInstFun do_ql inst_final ds_flag (fun_orig, rn_fun, fun_lspan) tc_fun fun_sigm |
| 706 | 702 | , text "args:" <+> ppr rn_args
|
| 707 | 703 | , text "do_ql" <+> ppr do_ql
|
| 708 | 704 | , text "ctx" <+> ppr fun_lspan])
|
| 709 | - ; res@(_, fun_ty) <- -- setQLInstLevel do_ql $ -- See (TCAPP1) and (TCAPP2) in
|
|
| 710 | - -- Note [tcApp: typechecking applications]
|
|
| 711 | - go 1 [] fun_sigma rn_args
|
|
| 705 | + ; res@(_, fun_ty) <- go 1 [] fun_sigma rn_args
|
|
| 712 | 706 | ; traceTc "tcInstFun:ret" (ppr fun_ty)
|
| 713 | 707 | ; return res
|
| 714 | 708 | }
|
| ... | ... | @@ -671,7 +671,7 @@ tcExpr expr@(RecordUpd { rupd_expr = record_expr |
| 671 | 671 | , recUpdFields = rbnds }
|
| 672 | 672 | })
|
| 673 | 673 | res_ty
|
| 674 | - = assert (notNull rbnds) $
|
|
| 674 | + = assert (notNull rbnds) $ mkExpandedExprTc expr <$>
|
|
| 675 | 675 | do { -- Expand the record update. See Note [Record Updates].
|
| 676 | 676 | |
| 677 | 677 | ; (ds_expr, ds_res_ty, err_msg)
|
| 1 | 1 | default-fail05.hs:11:10: error: [GHC-39999]
|
| 2 | - • Ambiguous type variable ‘t0’ arising from a use of ‘toList’
|
|
| 3 | - prevents the constraint ‘(Foldable t0)’ from being solved.
|
|
| 4 | - Probable fix: use a type annotation to specify what ‘t0’ should be.
|
|
| 2 | + • Ambiguous type variable ‘f0’ arising from a use of ‘toList’
|
|
| 3 | + prevents the constraint ‘(Foldable f0)’ from being solved.
|
|
| 4 | + Probable fix: use a type annotation to specify what ‘f0’ should be.
|
|
| 5 | 5 | Potentially matching instances:
|
| 6 | 6 | instance Foldable (Either a)
|
| 7 | 7 | -- Defined in ‘GHC.Internal.Data.Foldable’
|
| ... | ... | @@ -14,9 +14,9 @@ default-fail05.hs:11:10: error: [GHC-39999] |
| 14 | 14 | In a stmt of a 'do' block: print (toList $ pure 21)
|
| 15 | 15 | |
| 16 | 16 | default-fail05.hs:11:19: error: [GHC-39999]
|
| 17 | - • Ambiguous type variable ‘t0’ arising from a use of ‘pure’
|
|
| 18 | - prevents the constraint ‘(Applicative t0)’ from being solved.
|
|
| 19 | - Probable fix: use a type annotation to specify what ‘t0’ should be.
|
|
| 17 | + • Ambiguous type variable ‘f0’ arising from a use of ‘pure’
|
|
| 18 | + prevents the constraint ‘(Applicative f0)’ from being solved.
|
|
| 19 | + Probable fix: use a type annotation to specify what ‘f0’ should be.
|
|
| 20 | 20 | Potentially matching instances:
|
| 21 | 21 | instance Applicative IO -- Defined in ‘GHC.Internal.Base’
|
| 22 | 22 | instance Applicative Maybe -- Defined in ‘GHC.Internal.Base’
|
| ... | ... | @@ -28,11 +28,11 @@ default-fail05.hs:11:19: error: [GHC-39999] |
| 28 | 28 | In a stmt of a 'do' block: print (toList $ pure 21)
|
| 29 | 29 | |
| 30 | 30 | default-fail05.hs:12:3: error: [GHC-39999]
|
| 31 | - • Ambiguous type variable ‘t1’ arising from a use of ‘traverse’
|
|
| 32 | - prevents the constraint ‘(Traversable t1)’ from being solved.
|
|
| 31 | + • Ambiguous type variable ‘t0’ arising from a use of ‘traverse’
|
|
| 32 | + prevents the constraint ‘(Traversable t0)’ from being solved.
|
|
| 33 | 33 | Relevant bindings include
|
| 34 | - main :: IO (t1 ()) (bound at default-fail05.hs:10:1)
|
|
| 35 | - Probable fix: use a type annotation to specify what ‘t1’ should be.
|
|
| 34 | + main :: IO (t0 ()) (bound at default-fail05.hs:10:1)
|
|
| 35 | + Probable fix: use a type annotation to specify what ‘t0’ should be.
|
|
| 36 | 36 | Potentially matching instances:
|
| 37 | 37 | instance Traversable (Either a)
|
| 38 | 38 | -- Defined in ‘GHC.Internal.Data.Traversable’
|
| ... | ... | @@ -51,11 +51,11 @@ default-fail05.hs:12:3: error: [GHC-39999] |
| 51 | 51 | traverse print (pure 42)
|
| 52 | 52 | |
| 53 | 53 | default-fail05.hs:12:19: error: [GHC-39999]
|
| 54 | - • Ambiguous type variable ‘t1’ arising from a use of ‘pure’
|
|
| 55 | - prevents the constraint ‘(Applicative t1)’ from being solved.
|
|
| 54 | + • Ambiguous type variable ‘t0’ arising from a use of ‘pure’
|
|
| 55 | + prevents the constraint ‘(Applicative t0)’ from being solved.
|
|
| 56 | 56 | Relevant bindings include
|
| 57 | - main :: IO (t1 ()) (bound at default-fail05.hs:10:1)
|
|
| 58 | - Probable fix: use a type annotation to specify what ‘t1’ should be.
|
|
| 57 | + main :: IO (t0 ()) (bound at default-fail05.hs:10:1)
|
|
| 58 | + Probable fix: use a type annotation to specify what ‘t0’ should be.
|
|
| 59 | 59 | Potentially matching instances:
|
| 60 | 60 | instance Applicative IO -- Defined in ‘GHC.Internal.Base’
|
| 61 | 61 | instance Applicative Maybe -- Defined in ‘GHC.Internal.Base’
|
| 1 | 1 | T1897b.hs:16:1: error: [GHC-83865]
|
| 2 | - • Couldn't match type: Depend a0
|
|
| 3 | - with: Depend a
|
|
| 4 | - Expected: t (Depend a) -> Bool
|
|
| 5 | - Actual: t (Depend a0) -> Bool
|
|
| 2 | + • Couldn't match type: Depend b0
|
|
| 3 | + with: Depend b
|
|
| 4 | + Expected: t (Depend b) -> Bool
|
|
| 5 | + Actual: t (Depend b0) -> Bool
|
|
| 6 | 6 | Note: ‘Depend’ is a non-injective type family.
|
| 7 | - The type variable ‘a0’ is ambiguous
|
|
| 7 | + The type variable ‘b0’ is ambiguous
|
|
| 8 | 8 | • In the ambiguity check for the inferred type for ‘isValid’
|
| 9 | 9 | To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
|
| 10 | 10 | When checking the inferred type
|
| 11 | - isValid :: forall {t :: * -> *} {a}.
|
|
| 12 | - (Foldable t, Bug a) =>
|
|
| 13 | - t (Depend a) -> Bool
|
|
| 11 | + isValid :: forall {t :: * -> *} {b}.
|
|
| 12 | + (Foldable t, Bug b) =>
|
|
| 13 | + t (Depend b) -> Bool
|
|
| 14 | 14 |
| 1 | 1 | T14590.hs:4:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
|
| 2 | 2 | • Found hole: _ :: Int -> Int -> Int
|
| 3 | - • In the expression: x `_`
|
|
| 4 | - In the expression: (x `_`) y
|
|
| 3 | + • In the expression: (x `_`) y
|
|
| 5 | 4 | In an equation for ‘f1’: f1 x y = (x `_`) y
|
| 6 | 5 | • Relevant bindings include
|
| 7 | 6 | y :: Int (bound at T14590.hs:4:6)
|
| ... | ... | @@ -88,8 +87,7 @@ T14590.hs:4:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] |
| 88 | 87 | T14590.hs:5:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
|
| 89 | 88 | • Found hole: _a :: Int -> Int -> Int
|
| 90 | 89 | Or perhaps ‘_a’ is mis-spelled, or not in scope
|
| 91 | - • In the expression: x `_a`
|
|
| 92 | - In the expression: (x `_a`) y
|
|
| 90 | + • In the expression: (x `_a`) y
|
|
| 93 | 91 | In an equation for ‘f2’: f2 x y = (x `_a`) y
|
| 94 | 92 | • Relevant bindings include
|
| 95 | 93 | y :: Int (bound at T14590.hs:5:6)
|
| ... | ... | @@ -175,8 +173,7 @@ T14590.hs:5:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] |
| 175 | 173 | |
| 176 | 174 | T14590.hs:6:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
|
| 177 | 175 | • Found hole: _ :: Int -> Int -> Int
|
| 178 | - • In the expression: `_` x
|
|
| 179 | - In the expression: (`_` x) y
|
|
| 176 | + • In the expression: (`_` x) y
|
|
| 180 | 177 | In an equation for ‘f3’: f3 x y = (`_` x) y
|
| 181 | 178 | • Relevant bindings include
|
| 182 | 179 | y :: Int (bound at T14590.hs:6:6)
|
| ... | ... | @@ -263,8 +260,7 @@ T14590.hs:6:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] |
| 263 | 260 | T14590.hs:7:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
|
| 264 | 261 | • Found hole: _a :: Int -> Int -> Int
|
| 265 | 262 | Or perhaps ‘_a’ is mis-spelled, or not in scope
|
| 266 | - • In the expression: `_a` x
|
|
| 267 | - In the expression: (`_a` x) y
|
|
| 263 | + • In the expression: (`_a` x) y
|
|
| 268 | 264 | In an equation for ‘f4’: f4 x y = (`_a` x) y
|
| 269 | 265 | • Relevant bindings include
|
| 270 | 266 | y :: Int (bound at T14590.hs:7:6)
|
| ... | ... | @@ -23,5 +23,5 @@ T6069.hs:15:16: error: [GHC-83865] |
| 23 | 23 | Actual: (forall s. ST s b2) -> b2
|
| 24 | 24 | • In the second argument of ‘(.)’, namely ‘runST’
|
| 25 | 25 | In the first argument of ‘($)’, namely ‘(print . runST)’
|
| 26 | - In the expression: (print . runST) $
|
|
| 26 | + In the expression: ((print . runST) $) fourty_two
|
|
| 27 | 27 |
| 1 | 1 | T7857.hs:8:11: error: [GHC-39999]
|
| 2 | 2 | • Could not deduce ‘PrintfType a0’ arising from a use of ‘printf’
|
| 3 | - from the context: PrintfArg q
|
|
| 4 | - bound by the inferred type of g :: PrintfArg q => q -> b
|
|
| 3 | + from the context: PrintfArg t
|
|
| 4 | + bound by the inferred type of g :: PrintfArg t => t -> b
|
|
| 5 | 5 | at T7857.hs:8:1-21
|
| 6 | 6 | The type variable ‘a0’ is ambiguous
|
| 7 | 7 | Potentially matching instances:
|