[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: Refactoring: More consistently use logOutput, logInfo, fatalErrorMsg

Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: b2f6aad0 by Simon Hengel at 2025-09-03T04:36:10-04:00 Refactoring: More consistently use logOutput, logInfo, fatalErrorMsg - - - - - 60a16db7 by Rodrigo Mesquita at 2025-09-03T10:55:50+01:00 bytecode: Don't PUSH_L 0; SLIDE 1 1 While looking through bytecode I noticed a quite common unfortunate pattern: ... PUSH_L 0 SLIDE 1 1 We do this often by generically constructing a tail call from a function atom that may be somewhere arbitrary on the stack. However, for the special case that the function can be found directly on top of the stack, as part of the arguments, it's plain redundant to push then slide it. In this commit we add a small optimisation to the generation of tailcalls in bytecode. Simply: lookahead for the function in the stack. If it is the first thing on the stack and it is part of the arguments which would be dropped as we entered the tail call, then don't push then slide it. In a simple example (T26042b), this already produced a drastic improvement in generated code (left is old, right is with this patch): ```diff 3c3 < 2025-07-29 10:14:02.081277 UTC ---
2025-07-29 10:50:36.560949 UTC 160,161c160 < PUSH_L 0 < SLIDE 1 2
SLIDE 1 1
164,165d162 < PUSH_L 0 < SLIDE 1 1 175,176c172 < PUSH_L 0 < SLIDE 1 2 ---
SLIDE 1 1
179,180d174 < PUSH_L 0 < SLIDE 1 1 206,207d199 < PUSH_L 0 < SLIDE 1 1 210,211d201 < PUSH_L 0 < SLIDE 1 1 214,215d203 < PUSH_L 0 < SLIDE 1 1 218,219d205 < PUSH_L 0 < SLIDE 1 1 222,223d207 < PUSH_L 0 < SLIDE 1 1 ... 600,601c566 < PUSH_L 0 < SLIDE 1 2 ---
SLIDE 1 1
604,605d568 < PUSH_L 0 < SLIDE 1 1 632,633d594 < PUSH_L 0 < SLIDE 1 1 636,637d596 < PUSH_L 0 < SLIDE 1 1 640,641d598 < PUSH_L 0 < SLIDE 1 1 644,645d600 < PUSH_L 0 < SLIDE 1 1 648,649d602 < PUSH_L 0 < SLIDE 1 1 652,653d604 < PUSH_L 0 < SLIDE 1 1 656,657d606 < PUSH_L 0 < SLIDE 1 1 660,661d608 < PUSH_L 0 < SLIDE 1 1 664,665d610 < PUSH_L 0 < SLIDE 1 1 ``` I also compiled lib:Cabal to bytecode and counted the number of bytecode lines with `find dist-newstyle -name "*.dump-BCOs" -exec wc {} +`: with unoptimized core: 1190689 lines (before) - 1172891 lines (now) = 17798 less redundant instructions (-1.5% lines) with optimized core: 1924818 lines (before) - 1864836 lines (now) = 59982 less redundant instructions (-3.1% lines) - - - - - d0d56724 by L0neGamer at 2025-09-03T18:57:25-04:00 Add Control.Monad.thenM and Control.Applicative.thenA - - - - - 19 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Data/IOEnv.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Stg/Lint.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/Tc/Utils/Monad.hs - libraries/base/changelog.md - libraries/base/src/Control/Applicative.hs - libraries/base/src/Control/Monad.hs - libraries/ghc-internal/src/GHC/Internal/Base.hs - libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/profiling/should_run/callstack001.stdout Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -26,6 +26,7 @@ module GHC.Core.Lint ( -- ** Debug output EndPassConfig (..), endPassIO, + lintMessage, displayLintResults, dumpPassResult ) where @@ -309,11 +310,6 @@ path does not result in allocation in the hot path. This can be surprisingly impactful. Changing `lint_app` reduced allocations for one test program I was looking at by ~4%. -Note [MCInfo for Lint] -~~~~~~~~~~~~~~~~~~~~~~ -When printing a Lint message, use the MCInfo severity so that the -message is printed on stderr rather than stdout (#13342). - ************************************************************************ * * Beginning and ending passes @@ -321,6 +317,12 @@ message is printed on stderr rather than stdout (#13342). ************************************************************************ -} +lintMessage :: Logger -> SDoc -> IO () +lintMessage logger = + -- Note: Use logInfo when printing a Lint message, so that the message is + -- printed on stderr rather than stdout (#13342). + logInfo logger . withPprStyle defaultDumpStyle + -- | Configuration for boilerplate operations at the end of a -- compilation pass producing Core. data EndPassConfig = EndPassConfig @@ -436,8 +438,7 @@ displayLintResults :: Logger -> IO () displayLintResults logger display_warnings pp_what pp_pgm (warns, errs) | not (isEmptyBag errs) - = do { logMsg logger Err.MCInfo noSrcSpan -- See Note [MCInfo for Lint] - $ withPprStyle defaultDumpStyle + = do { lintMessage logger (vcat [ lint_banner "errors" pp_what, Err.pprMessageBag errs , text "*** Offending Program ***" , pp_pgm @@ -447,8 +448,7 @@ displayLintResults logger display_warnings pp_what pp_pgm (warns, errs) | not (isEmptyBag warns) , log_enable_debug (logFlags logger) , display_warnings - = logMsg logger Err.MCInfo noSrcSpan -- See Note [MCInfo for Lint] - $ withPprStyle defaultDumpStyle + = lintMessage logger (lint_banner "warnings" pp_what $$ Err.pprMessageBag (mapBag ($$ blankLine) warns)) | otherwise = return () ===================================== compiler/GHC/Data/IOEnv.hs ===================================== @@ -45,7 +45,7 @@ import Data.IORef ( IORef, newIORef, readIORef, writeIORef, modifyIORef, atomicModifyIORef, atomicModifyIORef' ) import System.IO.Unsafe ( unsafeInterleaveIO ) import System.IO ( fixIO ) -import Control.Monad +import Control.Monad ( MonadPlus ) import Control.Monad.Trans.Reader import Control.Monad.Catch (MonadCatch, MonadMask, MonadThrow) import GHC.Utils.Monad ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -18,6 +18,7 @@ import GHC.Prelude import GHC.Platform import GHC.ForeignSrcLang import GHC.Data.FastString +import GHC.Core.Lint ( lintMessage ) import GHC.CmmToAsm ( nativeCodeGen ) import GHC.CmmToLlvm ( llvmCodeGen ) @@ -55,7 +56,6 @@ import GHC.Utils.Panic.Plain ( pgmError ) import GHC.Unit import GHC.Unit.Finder ( mkStubPaths ) -import GHC.Types.SrcLoc import GHC.Types.CostCentre import GHC.Types.ForeignStubs import GHC.Types.Unique.DSM @@ -109,10 +109,7 @@ codeOutput logger tmpfs llvm_config dflags unit_state this_mod filenm location g (text "CmmLint"<+>brackets (ppr this_mod)) (const ()) $ do { case cmmLint (targetPlatform dflags) cmm of - Just err -> do { logMsg logger - MCInfo -- See Note [MCInfo for Lint] in "GHC.Core.Lint" - noSrcSpan - $ withPprStyle defaultDumpStyle err + Just err -> do { lintMessage logger err ; ghcExit logger 1 } Nothing -> return () ===================================== compiler/GHC/Driver/Pipeline/Execute.hs ===================================== @@ -1162,7 +1162,7 @@ getHCFilePackages filename = linkDynLibCheck :: Logger -> TmpFs -> DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO () linkDynLibCheck logger tmpfs dflags unit_env o_files dep_units = do when (haveRtsOptsFlags dflags) $ - logMsg logger MCInfo noSrcSpan + logInfo logger $ withPprStyle defaultUserStyle (text "Warning: -rtsopts and -with-rtsopts have no effect with -shared." $$ text " Call hs_init_ghc() from your main() function to set these options.") ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -1104,7 +1104,7 @@ For some background on this choice see #15269. showIface :: Logger -> DynFlags -> UnitState -> NameCache -> FilePath -> IO () showIface logger dflags unit_state name_cache filename = do let profile = targetProfile dflags - printer = logMsg logger MCOutput noSrcSpan . withPprStyle defaultDumpStyle + printer = logOutput logger . withPprStyle defaultDumpStyle -- skip the hi way check; we don't want to worry about profiled vs. -- non-profiled interfaces, for example. ===================================== compiler/GHC/Linker/Loader.hs ===================================== @@ -508,7 +508,7 @@ classifyLdInput logger platform f | isObjectFilename platform f = return (Just (Objects [f])) | isDynLibFilename platform f = return (Just (DLLPath f)) | otherwise = do - logMsg logger MCInfo noSrcSpan + logInfo logger $ withPprStyle defaultUserStyle (text ("Warning: ignoring unrecognised input `" ++ f ++ "'")) return Nothing ===================================== compiler/GHC/Stg/Lint.hs ===================================== @@ -104,6 +104,7 @@ import GHC.Stg.Utils import GHC.Core.DataCon import GHC.Core ( AltCon(..) ) import GHC.Core.Type +import GHC.Core.Lint ( lintMessage ) import GHC.Types.Basic ( TopLevelFlag(..), isTopLevel, isMarkedCbv ) import GHC.Types.CostCentre ( isCurrentCCS ) @@ -148,8 +149,7 @@ lintStgTopBindings platform logger diag_opts opts extra_vars this_mod unarised w Nothing -> return () Just msg -> do - logMsg logger Err.MCInfo noSrcSpan -- See Note [MCInfo for Lint] in "GHC.Core.Lint" - $ withPprStyle defaultDumpStyle + lintMessage logger (vcat [ text "*** Stg Lint ErrMsgs: in" <+> text whodunit <+> text "***", msg, ===================================== compiler/GHC/StgToByteCode.hs ===================================== @@ -748,12 +748,21 @@ doTailCall init_d s p fn args = do where do_pushes !d [] reps = do - assert (null reps) return () - (push_fn, sz) <- pushAtom d p (StgVarArg fn) platform <- profilePlatform <$> getProfile - assert (sz == wordSize platform) return () - let slide = mkSlideB platform (d - init_d + wordSize platform) (init_d - s) - return (push_fn `appOL` (slide `appOL` unitOL ENTER)) + assert (null reps) return () + case lookupBCEnv_maybe fn p of + Just d_v + | d - d_v == 0 -- shortcut; the first thing on the stack is what we want to enter, + , d_v <= init_d -- and it is between init_d and sequel (which will be dropped) + -> do + let slide = mkSlideB platform (d - init_d + wordSize platform) + (init_d - s - wordSize platform) + return (slide `appOL` unitOL ENTER) + _ -> do + (push_fn, sz) <- pushAtom d p (StgVarArg fn) + assert (sz == wordSize platform) return () + let slide = mkSlideB platform (d - init_d + wordSize platform) (init_d - s) + return (push_fn `appOL` (slide `appOL` unitOL ENTER)) do_pushes !d args reps = do let (push_apply, n, rest_of_reps) = findPushSeq reps (these_args, rest_of_args) = splitAt n args ===================================== compiler/GHC/Tc/Utils/Monad.hs ===================================== @@ -2351,8 +2351,7 @@ failIfM msg = do env <- getLclEnv let full_msg = (if_loc env <> colon) $$ nest 2 msg logger <- getLogger - liftIO (logMsg logger MCFatal - noSrcSpan $ withPprStyle defaultErrStyle full_msg) + liftIO $ fatalErrorMsg logger full_msg failM -------------------- @@ -2384,10 +2383,7 @@ forkM doc thing_inside logger <- getLogger let msg = hang (text "forkM failed:" <+> doc) 2 (text (show exn)) - liftIO $ logMsg logger - MCFatal - noSrcSpan - $ withPprStyle defaultErrStyle msg + liftIO $ fatalErrorMsg logger msg ; traceIf (text "} ending fork (badly)" <+> doc) ; pgmError "Cannot continue after interface file error" } } ===================================== libraries/base/changelog.md ===================================== @@ -6,6 +6,7 @@ * Fix issues with toRational for types capable to represent infinite and not-a-number values ([CLC proposal #338](https://github.com/haskell/core-libraries-committee/issues/338)) * Modify the implementation of `Data.List.sortOn` to use `(>)` instead of `compare`. ([CLC proposal #332](https://github.com/haskell/core-libraries-committee/issues/332)) * `GHC.Exts.IOPort#` and its related operations have been removed ([CLC #213](https://github.com/haskell/core-libraries-committee/issues/213)) + * Add `thenA` and `thenM`. ([CLC proposal #351](https://github.com/haskell/core-libraries-committee/issues/351)) * Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350)) * Remove extra laziness from `Data.Bifunctor.Bifunctor` instances for all tuples to have the same laziness as their `Data.Functor.Functor` counterparts (i.e. they became more strict than before) ([CLC proposal #339](https://github.com/haskell/core-libraries-committee/issues/339)) * Adjust the strictness of `Data.List.iterate'` to be more reasonable: every element of the output list is forced to WHNF when the `(:)` containing it is forced. ([CLC proposal #335)](https://github.com/haskell/core-libraries-committee/issues/335) ===================================== libraries/base/src/Control/Applicative.hs ===================================== @@ -49,6 +49,7 @@ module Control.Applicative ( liftA, liftA3, optional, asum, + thenA, ) where import GHC.Internal.Control.Category hiding ((.), id) ===================================== libraries/base/src/Control/Monad.hs ===================================== @@ -57,6 +57,7 @@ module Control.Monad liftM4, liftM5, ap, + thenM, -- ** Strict monadic functions (<$!>) ) where ===================================== libraries/ghc-internal/src/GHC/Internal/Base.hs ===================================== @@ -1223,6 +1223,9 @@ class Functor f => Applicative f where -- -- As such this function may be used to implement a `Functor` instance from an `Applicative` one. -- +-- This function can be used to define `fmap = liftA`, if `Applicative` is already +-- defined for a data type. +-- -- ==== __Examples__ -- Using the Applicative instance for Lists: -- @@ -1233,7 +1236,6 @@ class Functor f => Applicative f where -- -- >>> liftA (+1) (Just 3) -- Just 4 - liftA :: Applicative f => (a -> b) -> f a -> f b liftA f a = pure f <*> a -- Caution: since this may be used for `fmap`, we can't use the obvious @@ -1253,6 +1255,18 @@ liftA3 f a b c = liftA2 f a b <*> c {-# SPECIALISE liftA3 :: (a1->a2->a3->r) -> Maybe a1 -> Maybe a2 -> Maybe a3 -> Maybe r #-} +-- | Sequence two `Applicative` actions, discarding the result of the first one. +-- +-- Defined as `thenA fa fb = (id <$ fa) <*> fb`. +-- +-- This can be used to explicitly define `(*>) = thenA`, which is the default +-- definition. +-- +-- @since 4.23.0.0 +thenA :: Applicative f => f a -> f b -> f b +thenA fa fb = (id <$ fa) <*> fb +{-# INLINEABLE thenA #-} + -- | The 'join' function is the conventional monad join operator. It -- is used to remove one level of monadic structure, projecting its -- bound argument into the outer level. @@ -1453,12 +1467,18 @@ similar problems in nofib. -- | Promote a function to a monad. -- This is equivalent to 'fmap' but specialised to Monads. +-- +-- This function can be used to define `fmap = liftM`, if `Monad` is already +-- defined for a data type. liftM :: (Monad m) => (a1 -> r) -> m a1 -> m r liftM f m1 = do { x1 <- m1; return (f x1) } -- | Promote a function to a monad, scanning the monadic arguments from -- left to right. -- +-- This function can be used to define `liftA2 = liftM2`, if `Monad` is already +-- defined for a data type. +-- -- ==== __Examples__ -- -- >>> liftM2 (+) [0,1] [0,2] @@ -1514,6 +1534,9 @@ is equivalent to
liftM<n> f x1 x2 ... xn
+This function can be used to define `(<*>) = ap`, if `Monad` is already +defined for a data type. + ==== __Examples__
pure (\x y z -> x + y * z) `ap` Just 1 `ap` Just 5 `ap` Just 10 @@ -1527,6 +1550,17 @@ ap m1 m2 = do { x1 <- m1; x2 <- m2; return (x1 x2) } {-# SPECIALISE ap :: IO (a -> b) -> IO a -> IO b #-} {-# SPECIALISE ap :: Maybe (a -> b) -> Maybe a -> Maybe b #-}
+-- | Sequence two monadic actions, discarding the result of the first one. +-- +-- Defined as `thenM ma mb = ma >>= const mb`. +-- +-- This can be used to define `(*>) = thenM`. +-- +-- @since 4.23.0.0 +thenM :: (Monad m) => m a -> m b -> m b +thenM ma mb = ma >>= const mb +{-# INLINEABLE thenM #-} + -- instances for Prelude types -- | @since base-2.01 ===================================== libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs ===================================== @@ -71,6 +71,8 @@ module GHC.Internal.Control.Monad , ap + , thenM + -- ** Strict monadic functions , (<$!>) ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -34,6 +34,7 @@ module Control.Applicative where liftA :: forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b liftA3 :: forall (f :: * -> *) a b c d. Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d optional :: forall (f :: * -> *) a. Alternative f => f a -> f (GHC.Internal.Maybe.Maybe a) + thenA :: forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b module Control.Arrow where -- Safety: Safe @@ -483,6 +484,7 @@ module Control.Monad where replicateM_ :: forall (m :: * -> *) a. GHC.Internal.Base.Applicative m => GHC.Internal.Types.Int -> m a -> m () sequence :: forall (t :: * -> *) (m :: * -> *) a. (GHC.Internal.Data.Traversable.Traversable t, Monad m) => t (m a) -> m (t a) sequence_ :: forall (t :: * -> *) (m :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, Monad m) => t (m a) -> m () + thenM :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b unless :: forall (f :: * -> *). GHC.Internal.Base.Applicative f => GHC.Internal.Types.Bool -> f () -> f () void :: forall (f :: * -> *) a. Functor f => f a -> f () when :: forall (f :: * -> *). GHC.Internal.Base.Applicative f => GHC.Internal.Types.Bool -> f () -> f () ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -34,6 +34,7 @@ module Control.Applicative where liftA :: forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b liftA3 :: forall (f :: * -> *) a b c d. Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d optional :: forall (f :: * -> *) a. Alternative f => f a -> f (GHC.Internal.Maybe.Maybe a) + thenA :: forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b module Control.Arrow where -- Safety: Safe @@ -483,6 +484,7 @@ module Control.Monad where replicateM_ :: forall (m :: * -> *) a. GHC.Internal.Base.Applicative m => GHC.Internal.Types.Int -> m a -> m () sequence :: forall (t :: * -> *) (m :: * -> *) a. (GHC.Internal.Data.Traversable.Traversable t, Monad m) => t (m a) -> m (t a) sequence_ :: forall (t :: * -> *) (m :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, Monad m) => t (m a) -> m () + thenM :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b unless :: forall (f :: * -> *). GHC.Internal.Base.Applicative f => GHC.Internal.Types.Bool -> f () -> f () void :: forall (f :: * -> *) a. Functor f => f a -> f () when :: forall (f :: * -> *). GHC.Internal.Base.Applicative f => GHC.Internal.Types.Bool -> f () -> f () ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -34,6 +34,7 @@ module Control.Applicative where liftA :: forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b liftA3 :: forall (f :: * -> *) a b c d. Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d optional :: forall (f :: * -> *) a. Alternative f => f a -> f (GHC.Internal.Maybe.Maybe a) + thenA :: forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b module Control.Arrow where -- Safety: Safe @@ -483,6 +484,7 @@ module Control.Monad where replicateM_ :: forall (m :: * -> *) a. GHC.Internal.Base.Applicative m => GHC.Internal.Types.Int -> m a -> m () sequence :: forall (t :: * -> *) (m :: * -> *) a. (GHC.Internal.Data.Traversable.Traversable t, Monad m) => t (m a) -> m (t a) sequence_ :: forall (t :: * -> *) (m :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, Monad m) => t (m a) -> m () + thenM :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b unless :: forall (f :: * -> *). GHC.Internal.Base.Applicative f => GHC.Internal.Types.Bool -> f () -> f () void :: forall (f :: * -> *) a. Functor f => f a -> f () when :: forall (f :: * -> *). GHC.Internal.Base.Applicative f => GHC.Internal.Types.Bool -> f () -> f () ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -34,6 +34,7 @@ module Control.Applicative where liftA :: forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b liftA3 :: forall (f :: * -> *) a b c d. Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d optional :: forall (f :: * -> *) a. Alternative f => f a -> f (GHC.Internal.Maybe.Maybe a) + thenA :: forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b module Control.Arrow where -- Safety: Safe @@ -483,6 +484,7 @@ module Control.Monad where replicateM_ :: forall (m :: * -> *) a. GHC.Internal.Base.Applicative m => GHC.Internal.Types.Int -> m a -> m () sequence :: forall (t :: * -> *) (m :: * -> *) a. (GHC.Internal.Data.Traversable.Traversable t, Monad m) => t (m a) -> m (t a) sequence_ :: forall (t :: * -> *) (m :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, Monad m) => t (m a) -> m () + thenM :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b unless :: forall (f :: * -> *). GHC.Internal.Base.Applicative f => GHC.Internal.Types.Bool -> f () -> f () void :: forall (f :: * -> *) a. Functor f => f a -> f () when :: forall (f :: * -> *). GHC.Internal.Base.Applicative f => GHC.Internal.Types.Bool -> f () -> f () ===================================== testsuite/tests/profiling/should_run/callstack001.stdout ===================================== @@ -1,2 +1,2 @@ -["GHC.Internal.TopHandler.runMainIO1 (<no location info>)","Main.main (callstack001.hs:17:8-21)","Main.mapM (callstack001.hs:10:13-17)","Main.mapM.go (callstack001.hs:(12,21)-(15,25))","Main.mapM.go (callstack001.hs:13:17-19)","Main.f (callstack001.hs:7:7-49)","Main.f (callstack001.hs:7:10-35)","GHC.Internal.Base.>>= (libraries/ghc-internal/src/GHC/Internal/Base.hs:1350:5-55)","GHC.Internal.Base.$fMonadIO1 (<no location info>)","GHC.Internal.Stack.CCS.currentCallStack (libraries/ghc-internal/src/GHC/Internal/Stack/CCS.hsc:126:1-16)","GHC.Internal.Stack.CCS.currentCallStack1 (<no location info>)"] -["GHC.Internal.TopHandler.runMainIO1 (<no location info>)","Main.main (callstack001.hs:17:8-21)","Main.mapM (callstack001.hs:10:13-17)","Main.mapM.go (callstack001.hs:(12,21)-(15,25))","GHC.Internal.Base.>>= (libraries/ghc-internal/src/GHC/Internal/Base.hs:1350:5-55)","GHC.Internal.Base.$fMonadIO1 (<no location info>)","GHC.Internal.Stack.CCS.currentCallStack (libraries/ghc-internal/src/GHC/Internal/Stack/CCS.hsc:126:1-16)","GHC.Internal.Stack.CCS.currentCallStack1 (<no location info>)"] +["GHC.Internal.TopHandler.runMainIO1 (<no location info>)","Main.main (callstack001.hs:17:8-21)","Main.mapM (callstack001.hs:10:13-17)","Main.mapM.go (callstack001.hs:(12,21)-(15,25))","Main.mapM.go (callstack001.hs:13:17-19)","Main.f (callstack001.hs:7:7-49)","Main.f (callstack001.hs:7:10-35)","GHC.Internal.Base.>>= (libraries/ghc-internal/src/GHC/Internal/Base.hs:1364:5-55)","GHC.Internal.Base.$fMonadIO1 (<no location info>)","GHC.Internal.Stack.CCS.currentCallStack (libraries/ghc-internal/src/GHC/Internal/Stack/CCS.hsc:126:1-16)","GHC.Internal.Stack.CCS.currentCallStack1 (<no location info>)"] +["GHC.Internal.TopHandler.runMainIO1 (<no location info>)","Main.main (callstack001.hs:17:8-21)","Main.mapM (callstack001.hs:10:13-17)","Main.mapM.go (callstack001.hs:(12,21)-(15,25))","GHC.Internal.Base.>>= (libraries/ghc-internal/src/GHC/Internal/Base.hs:1364:5-55)","GHC.Internal.Base.$fMonadIO1 (<no location info>)","GHC.Internal.Stack.CCS.currentCallStack (libraries/ghc-internal/src/GHC/Internal/Stack/CCS.hsc:126:1-16)","GHC.Internal.Stack.CCS.currentCallStack1 (<no location info>)"] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fa557b8706ddf89b28f87675dcbded2... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fa557b8706ddf89b28f87675dcbded2... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)