Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: 2003c4ab by Apoorv Ingle at 2025-11-24T10:04:35-06:00 look through applications to check if we need deepsubsumption - - - - - 7 changed files: - compiler/GHC/CmmToAsm.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Tc/Gen/App.hs - + testsuite/tests/typecheck/should_compile/ExpansionQLIm.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T7857.stderr - testsuite/tests/typecheck/should_fail/tcfail181.stderr Changes: ===================================== compiler/GHC/CmmToAsm.hs ===================================== @@ -1,4 +1,3 @@ -{-# LANGUAGE DeepSubsumption #-} -- ----------------------------------------------------------------------------- -- -- (c) The University of Glasgow 1993-2004 ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1157,7 +1157,8 @@ the typechecker: * HsDo, where we give the SrcSpan of the entire do block to each ApplicativeStmt. * Expanded (via ExpandedThingRn) ExplicitList{}, where we give the SrcSpan of the original - list expression to the 'fromListN' call. + list expression to the expanded expression. The 'fromListN' is assigned + a generated location span In order for the implicit function calls to not be confused for actual occurrences of functions in the source code, most of this extra information ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -486,11 +486,18 @@ getDeepSubsumptionFlag_DataConHead app_head = ; return $ if | user_ds -> Deep DeepSub - | XExpr (ConLikeTc (RealDataCon {})) <- app_head - -> Deep TopSub | otherwise - -> Shallow - } + -> go app_head + } + where + go :: HsExpr GhcTc -> DeepSubsumptionFlag + go app_head + | XExpr (ConLikeTc (RealDataCon {})) <- app_head + = Deep TopSub + | HsApp _ f _ <- app_head + = go (unLoc f) + | otherwise + = Shallow finishApp :: (HsExpr GhcTc, SrcSpan) -> [HsExprArg 'TcpTc] -> TcRhoType -> HsWrapper ===================================== testsuite/tests/typecheck/should_compile/ExpansionQLIm.hs ===================================== @@ -0,0 +1,10 @@ +module Test where + + +qqqq :: [String] +qqqq = (show (1 :: Int) :) $ ["2"] + +main :: IO () +main = do + putStrLn "abc" + putStrLn $ concat qqqq ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -658,8 +658,8 @@ def onlyHsParLocs(x): """ ls = x.split("\n") filteredLines = (loc.strip() for (loc,hspar) in zip(ls,ls[5:]) - if hspar.strip().startswith("(HsPar") - and not "<no location info>" in loc) + if hspar.strip().startswith("(HsPar") + and not "<no location info>" in loc) return '\n'.join(filteredLines) test('T15242', normalise_errmsg_fun(onlyHsParLocs), compile, ['']) test('T15431', normal, compile, ['']) @@ -957,3 +957,4 @@ test('T17705', normal, compile, ['']) test('T14745', normal, compile, ['']) test('T26451', normal, compile, ['']) test('T26582', normal, compile, ['']) +test('ExpansionQLIm', normal, compile, ['']) ===================================== testsuite/tests/typecheck/should_fail/T7857.stderr ===================================== @@ -1,8 +1,7 @@ - T7857.hs:8:11: error: [GHC-39999] • Could not deduce ‘PrintfType a0’ arising from a use of ‘printf’ - from the context: PrintfArg t - bound by the inferred type of g :: PrintfArg t => t -> b + from the context: PrintfArg q + bound by the inferred type of g :: PrintfArg q => q -> b at T7857.hs:8:1-21 The type variable ‘a0’ is ambiguous Potentially matching instances: @@ -15,3 +14,4 @@ T7857.hs:8:11: error: [GHC-39999] • In the second argument of ‘($)’, namely ‘printf "" i’ In the expression: f $ printf "" i In an equation for ‘g’: g i = f $ printf "" i + ===================================== testsuite/tests/typecheck/should_fail/tcfail181.stderr ===================================== @@ -1,5 +1,5 @@ tcfail181.hs:17:9: error: [GHC-39999] - • Could not deduce ‘Monad m0’ arising from a record update + • Could not deduce ‘Monad m0’ arising from a use of ‘foo’ from the context: Monad m bound by the inferred type of wog :: Monad m => p -> Something (m Bool) e View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2003c4abed79548f64a4bfb760960894... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2003c4abed79548f64a4bfb760960894... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Apoorv Ingle (@ani)