[Git][ghc/ghc][wip/spj-apporv-Oct24] wrap expanded records in an XExpr. Accept test cases
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 wrap expanded records in an XExpr. Accept test cases - - - - - 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: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -679,10 +679,6 @@ quickLookKeys = [dollarIdKey, leftSectionKey, rightSectionKey] * * ********************************************************************* -} --- setQLInstLevel :: QLFlag -> TcM a -> TcM a --- setQLInstLevel DoQL thing_inside = setTcLevel QLInstVar thing_inside --- setQLInstLevel NoQL thing_inside = thing_inside - tcInstFun :: QLFlag -> Bool -- False <=> Instantiate only /top-level, inferred/ variables; -- 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 , text "args:" <+> ppr rn_args , text "do_ql" <+> ppr do_ql , text "ctx" <+> ppr fun_lspan]) - ; res@(_, fun_ty) <- -- setQLInstLevel do_ql $ -- See (TCAPP1) and (TCAPP2) in - -- Note [tcApp: typechecking applications] - go 1 [] fun_sigma rn_args + ; res@(_, fun_ty) <- go 1 [] fun_sigma rn_args ; traceTc "tcInstFun:ret" (ppr fun_ty) ; return res } ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -671,7 +671,7 @@ tcExpr expr@(RecordUpd { rupd_expr = record_expr , recUpdFields = rbnds } }) res_ty - = assert (notNull rbnds) $ + = assert (notNull rbnds) $ mkExpandedExprTc expr <$> do { -- Expand the record update. See Note [Record Updates]. ; (ds_expr, ds_res_ty, err_msg) ===================================== testsuite/tests/default/default-fail05.stderr ===================================== @@ -1,7 +1,7 @@ default-fail05.hs:11:10: error: [GHC-39999] - • Ambiguous type variable ‘t0’ arising from a use of ‘toList’ - prevents the constraint ‘(Foldable t0)’ from being solved. - Probable fix: use a type annotation to specify what ‘t0’ should be. + • Ambiguous type variable ‘f0’ arising from a use of ‘toList’ + prevents the constraint ‘(Foldable f0)’ from being solved. + Probable fix: use a type annotation to specify what ‘f0’ should be. Potentially matching instances: instance Foldable (Either a) -- Defined in ‘GHC.Internal.Data.Foldable’ @@ -14,9 +14,9 @@ default-fail05.hs:11:10: error: [GHC-39999] In a stmt of a 'do' block: print (toList $ pure 21) default-fail05.hs:11:19: error: [GHC-39999] - • Ambiguous type variable ‘t0’ arising from a use of ‘pure’ - prevents the constraint ‘(Applicative t0)’ from being solved. - Probable fix: use a type annotation to specify what ‘t0’ should be. + • Ambiguous type variable ‘f0’ arising from a use of ‘pure’ + prevents the constraint ‘(Applicative f0)’ from being solved. + Probable fix: use a type annotation to specify what ‘f0’ should be. Potentially matching instances: instance Applicative IO -- Defined in ‘GHC.Internal.Base’ instance Applicative Maybe -- Defined in ‘GHC.Internal.Base’ @@ -28,11 +28,11 @@ default-fail05.hs:11:19: error: [GHC-39999] In a stmt of a 'do' block: print (toList $ pure 21) default-fail05.hs:12:3: error: [GHC-39999] - • Ambiguous type variable ‘t1’ arising from a use of ‘traverse’ - prevents the constraint ‘(Traversable t1)’ from being solved. + • Ambiguous type variable ‘t0’ arising from a use of ‘traverse’ + prevents the constraint ‘(Traversable t0)’ from being solved. Relevant bindings include - main :: IO (t1 ()) (bound at default-fail05.hs:10:1) - Probable fix: use a type annotation to specify what ‘t1’ should be. + main :: IO (t0 ()) (bound at default-fail05.hs:10:1) + Probable fix: use a type annotation to specify what ‘t0’ should be. Potentially matching instances: instance Traversable (Either a) -- Defined in ‘GHC.Internal.Data.Traversable’ @@ -51,11 +51,11 @@ default-fail05.hs:12:3: error: [GHC-39999] traverse print (pure 42) default-fail05.hs:12:19: error: [GHC-39999] - • Ambiguous type variable ‘t1’ arising from a use of ‘pure’ - prevents the constraint ‘(Applicative t1)’ from being solved. + • Ambiguous type variable ‘t0’ arising from a use of ‘pure’ + prevents the constraint ‘(Applicative t0)’ from being solved. Relevant bindings include - main :: IO (t1 ()) (bound at default-fail05.hs:10:1) - Probable fix: use a type annotation to specify what ‘t1’ should be. + main :: IO (t0 ()) (bound at default-fail05.hs:10:1) + Probable fix: use a type annotation to specify what ‘t0’ should be. Potentially matching instances: instance Applicative IO -- Defined in ‘GHC.Internal.Base’ instance Applicative Maybe -- Defined in ‘GHC.Internal.Base’ ===================================== testsuite/tests/indexed-types/should_fail/T1897b.stderr ===================================== @@ -1,14 +1,14 @@ T1897b.hs:16:1: error: [GHC-83865] - • Couldn't match type: Depend a0 - with: Depend a - Expected: t (Depend a) -> Bool - Actual: t (Depend a0) -> Bool + • Couldn't match type: Depend b0 + with: Depend b + Expected: t (Depend b) -> Bool + Actual: t (Depend b0) -> Bool Note: ‘Depend’ is a non-injective type family. - The type variable ‘a0’ is ambiguous + The type variable ‘b0’ is ambiguous • In the ambiguity check for the inferred type for ‘isValid’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes When checking the inferred type - isValid :: forall {t :: * -> *} {a}. - (Foldable t, Bug a) => - t (Depend a) -> Bool + isValid :: forall {t :: * -> *} {b}. + (Foldable t, Bug b) => + t (Depend b) -> Bool ===================================== testsuite/tests/typecheck/should_compile/T14590.stderr ===================================== @@ -1,7 +1,6 @@ T14590.hs:4:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] • Found hole: _ :: Int -> Int -> Int - • In the expression: x `_` - In the expression: (x `_`) y + • In the expression: (x `_`) y In an equation for ‘f1’: f1 x y = (x `_`) y • Relevant bindings include y :: Int (bound at T14590.hs:4:6) @@ -88,8 +87,7 @@ T14590.hs:4:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] T14590.hs:5:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] • Found hole: _a :: Int -> Int -> Int Or perhaps ‘_a’ is mis-spelled, or not in scope - • In the expression: x `_a` - In the expression: (x `_a`) y + • In the expression: (x `_a`) y In an equation for ‘f2’: f2 x y = (x `_a`) y • Relevant bindings include y :: Int (bound at T14590.hs:5:6) @@ -175,8 +173,7 @@ T14590.hs:5:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] T14590.hs:6:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] • Found hole: _ :: Int -> Int -> Int - • In the expression: `_` x - In the expression: (`_` x) y + • In the expression: (`_` x) y In an equation for ‘f3’: f3 x y = (`_` x) y • Relevant bindings include y :: Int (bound at T14590.hs:6:6) @@ -263,8 +260,7 @@ T14590.hs:6:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] T14590.hs:7:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] • Found hole: _a :: Int -> Int -> Int Or perhaps ‘_a’ is mis-spelled, or not in scope - • In the expression: `_a` x - In the expression: (`_a` x) y + • In the expression: (`_a` x) y In an equation for ‘f4’: f4 x y = (`_a` x) y • Relevant bindings include y :: Int (bound at T14590.hs:7:6) ===================================== testsuite/tests/typecheck/should_fail/T6069.stderr ===================================== @@ -23,5 +23,5 @@ T6069.hs:15:16: error: [GHC-83865] Actual: (forall s. ST s b2) -> b2 • In the second argument of ‘(.)’, namely ‘runST’ In the first argument of ‘($)’, namely ‘(print . runST)’ - In the expression: (print . runST) $ + In the expression: ((print . runST) $) fourty_two ===================================== testsuite/tests/typecheck/should_fail/T7857.stderr ===================================== @@ -1,7 +1,7 @@ T7857.hs:8:11: error: [GHC-39999] • Could not deduce ‘PrintfType a0’ arising from a use of ‘printf’ - from the context: PrintfArg q - bound by the inferred type of g :: PrintfArg q => q -> b + from the context: PrintfArg t + bound by the inferred type of g :: PrintfArg t => t -> b at T7857.hs:8:1-21 The type variable ‘a0’ is ambiguous Potentially matching instances: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d9e481eef6d66164a3c597c455d88bb6... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d9e481eef6d66164a3c597c455d88bb6... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Apoorv Ingle (@ani)