From gitlab at gitlab.haskell.org Thu Feb 1 06:08:38 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Thu, 01 Feb 2024 01:08:38 -0500 Subject: [Git][ghc/ghc][wip/ghc-internals-move] Move `base` to `ghc-internal` Message-ID: <65bb35664ad17_205b5b878fa208649@gitlab.mail> Ben Gamari pushed to branch wip/ghc-internals-move at Glasgow Haskell Compiler / GHC Commits: bf63f580 by Ben Gamari at 2024-01-31T22:07:12-08:00 Move `base` to `ghc-internal` Here we move a good deal of the implementation of `base` into a new package, `ghc-internal` such that it can be evolved independently from the user-visible interfaces of `base`. While we want to isolate implementation from interfaces, naturally, we would like to avoid turning `base` into a mere set of module re-exports. However, this is a non-trivial undertaking for a variety of reasons: * `base` contains numerous known-key and wired-in things, requiring corresponding changes in the compiler * `base` contains a significant amount of C code and corresponding autoconf logic, which is very fragile and difficult to break apart * `base` has numerous import cycles, which are currently dealt with via carefully balanced `hs-boot` files * We must not break existing users To accomplish this migration, I tried the following approaches: * [Split-GHC.Base]: Break apart the GHC.Base knot to allow incremental migration of modules into ghc-internal: this knot is simply too intertwined to be easily pulled apart, especially given the rather tricky import cycles that it contains) * [Move-Core]: Moving the "core" connected component of base (roughly 150 modules) into ghc-internal. While the Haskell side of this seems tractable, the C dependencies are very subtle to break apart. * [Move-Incrementally]: 1. Move all of base into ghc-internal 2. Examine the module structure and begin moving obvious modules (e.g. leaves of the import graph) back into base 3. Examine the modules remaining in ghc-internal, refactor as necessary to facilitate further moves 4. Go to (2) iterate until the cost/benefit of further moves is insufficient to justify continuing 5. Rename the modules moved into ghc-internal to ensure that they don't overlap with those in base 6. For each module moved into ghc-internal, add a shim module to base with the declarations which should be exposed and any requisite Haddocks (thus guaranteeing that base will be insulated from changes in the export lists of modules in ghc-internal Here I am using the [Move-Incrementally] approach, which is empirically the least painful of the unpleasant options above Metric Decrease: haddock.Cabal haddock.base Metric Increase: MultiComponentModulesRecomp T16875 - - - - - 30 changed files: - .gitignore - compiler/GHC/Builtin/Names.hs - compiler/GHC/StgToJS/Rts/Rts.hs - compiler/GHC/Unit/Types.hs - configure.ac - libraries/base/base.cabal - libraries/base/src/Control/Applicative.hs - libraries/base/src/Control/Concurrent.hs - libraries/base/src/Data/Complex.hs - libraries/base/src/Data/Semigroup.hs - + libraries/base/src/Dummy.hs - libraries/base/src/System/CPUTime/Posix/Times.hsc - libraries/base/.authorspellings → libraries/ghc-internal/.authorspellings - libraries/base/.gitignore → libraries/ghc-internal/.gitignore - libraries/base/.hlint.yaml → libraries/ghc-internal/.hlint.yaml - libraries/ghc-internal/LICENSE - libraries/base/Setup.hs → libraries/ghc-internal/Setup.hs - libraries/base/aclocal.m4 → libraries/ghc-internal/aclocal.m4 - libraries/base/cbits/CastFloatWord.cmm → libraries/ghc-internal/cbits/CastFloatWord.cmm - libraries/base/cbits/DarwinUtils.c → libraries/ghc-internal/cbits/DarwinUtils.c - libraries/base/cbits/IOutils.c → libraries/ghc-internal/cbits/IOutils.c - libraries/base/cbits/PrelIOUtils.c → libraries/ghc-internal/cbits/PrelIOUtils.c - libraries/base/cbits/SetEnv.c → libraries/ghc-internal/cbits/SetEnv.c - libraries/base/cbits/StackCloningDecoding.cmm → libraries/ghc-internal/cbits/StackCloningDecoding.cmm - libraries/base/cbits/Win32Utils.c → libraries/ghc-internal/cbits/Win32Utils.c - libraries/base/cbits/consUtils.c → libraries/ghc-internal/cbits/consUtils.c - libraries/base/cbits/iconv.c → libraries/ghc-internal/cbits/iconv.c - libraries/base/cbits/inputReady.c → libraries/ghc-internal/cbits/inputReady.c - libraries/base/cbits/md5.c → libraries/ghc-internal/cbits/md5.c - libraries/base/cbits/primFloat.c → libraries/ghc-internal/cbits/primFloat.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bf63f580f4bd020adae8b0073dd06916db6493d3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bf63f580f4bd020adae8b0073dd06916db6493d3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 06:15:54 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Thu, 01 Feb 2024 01:15:54 -0500 Subject: [Git][ghc/ghc][wip/T24344] base: Use strerror_r instead of strerror Message-ID: <65bb371a1d05_205b5b8bf179487787@gitlab.mail> Ben Gamari pushed to branch wip/T24344 at Glasgow Haskell Compiler / GHC Commits: 25414288 by Ben Gamari at 2024-02-01T01:15:46-05:00 base: Use strerror_r instead of strerror As noted by #24344, `strerror` is not necessarily thread-safe. Thankfully, POSIX.1-2001 has long offered `strerror_r`, which is safe to use. Fixes #24344. - - - - - 4 changed files: - libraries/base/base.cabal - + libraries/base/cbits/strerror.c - libraries/base/configure.ac - libraries/base/src/Foreign/C/Error.hs Changes: ===================================== libraries/base/base.cabal ===================================== @@ -376,6 +376,7 @@ Library cbits/primFloat.c cbits/sysconf.c cbits/fs.c + cbits/strerror.c cmm-sources: cbits/CastFloatWord.cmm ===================================== libraries/base/cbits/strerror.c ===================================== @@ -0,0 +1,29 @@ +// glibc will only expose the POSIX strerror_r if this is defined. +#define _POSIX_C_SOURCE 200112L + +#include +#include + +// This must be included after lest _GNU_SOURCE may be defined. +#include "HsBaseConfig.h" + +// returns zero on success +int base_strerror_r(int errnum, char *ptr, size_t buflen) +{ +#if defined(HAVE_STRERROR_R) + int ret = strerror_r(errnum, ptr, buflen); + if (ret == ERANGE) { + // Ellipsize the error + ptr[buflen-4] = '.'; + ptr[buflen-3] = '.'; + ptr[buflen-2] = '.'; + ret = 0; + } + return ret; +#elif defined(HAVE_STRERROR_S) + strerror_s(ptr, buflen, errnum); + return 0; +#else +#error neither strerror_r nor strerror_s are supported +#endif +} ===================================== libraries/base/configure.ac ===================================== @@ -41,6 +41,12 @@ AC_CHECK_DECLS([CLOCK_PROCESS_CPUTIME_ID], [], [], [[#include ]]) AC_CHECK_FUNCS([getclock getrusage times]) AC_CHECK_FUNCS([_chsize_s ftruncate]) +AC_CHECK_FUNCS([strerror_r strerror_s]) + +if test "$ac_cv_func_strerror_r" = no && test "$ac_cv_func_strerror_s" = no; then + AC_MSG_ERROR([Either strerror_r or strerror_s must be available]) +fi + # event-related fun # The line below already defines HAVE_KQUEUE and HAVE_POLL, so technically some of the # subsequent portions that redefine them could be skipped. However, we keep those portions ===================================== libraries/base/src/Foreign/C/Error.hs ===================================== @@ -91,6 +91,7 @@ module Foreign.C.Error ( #include "HsBaseConfig.h" import Foreign.Ptr +import Foreign.Marshal.Alloc import Foreign.C.Types import Foreign.C.String import Data.Functor ( void ) @@ -460,6 +461,20 @@ throwErrnoPathIfMinus1_ = throwErrnoPathIf_ (== -1) -- conversion of an "errno" value into IO error -- -------------------------------------------- +foreign import ccall "base_strerror_r" + c_strerror_r :: Errno -> Ptr CChar -> CSize -> IO CInt + +errnoToString :: Errno -> IO String +errnoToString errno = + allocaBytes len $ \ptr -> do + ret <- c_strerror_r errno ptr len + if ret /= 0 + then return "errnoToString failed" + else peekCString ptr + where + len :: Num a => a + len = 512 + -- | Construct an 'IOError' based on the given 'Errno' value. -- The optional information can be used to improve the accuracy of -- error messages. @@ -470,7 +485,7 @@ errnoToIOError :: String -- ^ the location where the error occurred -> Maybe String -- ^ optional filename associated with the error -> IOError errnoToIOError loc errno maybeHdl maybeName = unsafePerformIO $ do - str <- strerror errno >>= peekCString + str <- errnoToString errno return (IOError maybeHdl errType loc str (Just errno') maybeName) where Errno errno' = errno @@ -576,5 +591,3 @@ errnoToIOError loc errno maybeHdl maybeName = unsafePerformIO $ do | errno == eXDEV = UnsupportedOperation | otherwise = OtherError -foreign import ccall unsafe "string.h" strerror :: Errno -> IO (Ptr CChar) - View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2541428839c96f0e7e7a5d4960ba31f860005387 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2541428839c96f0e7e7a5d4960ba31f860005387 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 07:35:40 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 01 Feb 2024 02:35:40 -0500 Subject: [Git][ghc/ghc][wip/romes/24324] Work around autotools setting C11 standard in CC/CXX Message-ID: <65bb49cc852c0_205b5baab95649119a@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/24324 at Glasgow Haskell Compiler / GHC Commits: dab53ea1 by Rodrigo Mesquita at 2024-02-01T07:35:29+00:00 Work around autotools setting C11 standard in CC/CXX In autoconf >=2.70, C11 is set by default for $CC and $CXX via the -std=...11 flag. In this patch, we split the "-std" flag out of the $CC and $CXX variables, which we traditionally assume to be just the executable name/path, and move it to $CFLAGS/$CXXFLAGS instead. Fixes #24324 - - - - - 2 changed files: - configure.ac - + m4/fp_prog_move_to_flags.m4 Changes: ===================================== configure.ac ===================================== @@ -417,6 +417,9 @@ dnl detect compiler (prefer gcc over clang) and set $CC (unless CC already set), dnl later CC is copied to CC_STAGE{1,2,3} AC_PROG_CC([cc gcc clang]) AC_PROG_CXX([g++ clang++ c++]) +# Work around #24324 +MOVE_TO_FLAGS([CC],[CFLAGS]) +MOVE_TO_FLAGS([CXX],[CXXFLAGS]) MAYBE_OVERRIDE_STAGE0([ar],[AR_STAGE0]) ===================================== m4/fp_prog_move_to_flags.m4 ===================================== @@ -0,0 +1,19 @@ +# MOVE_TO_FLAGS +# -------------------------------- +# Split off flags from $1 (the compiler) to $2 (the flags). +# This works around autoconf setting $CC and $CXX to be a program plus the C11 +# `-std=...11` flag (#24324), starting from autotools 2.70. +AC_DEFUN([MOVE_TO_FLAGS],[ + +dnl Use IFS=' ' to split off the command from the arguments in $1. +dnl By expanding $$1, set accounts for quoting correctly, such that splitting +dnl e.g. '"A B/C" D' results in "A B/C" and "D". +tmp_IFS="$IFS" +IFS=' ' +eval set -- $$1 +IFS="$tmp_IFS" + +$1="[$]1" +shift +$2="[$]@ $$2" +]) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dab53ea1188e04fc3e75b7cc7df73f0323aa8d9f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dab53ea1188e04fc3e75b7cc7df73f0323aa8d9f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 09:34:55 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Thu, 01 Feb 2024 04:34:55 -0500 Subject: [Git][ghc/ghc][wip/T24251] 2 commits: Stop dropping a case whose binder is demanded Message-ID: <65bb65bfca813_12c9d11532d0699bf@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24251 at Glasgow Haskell Compiler / GHC Commits: 3b7be722 by Simon Peyton Jones at 2024-02-01T09:34:39+00:00 Stop dropping a case whose binder is demanded This MR fixes #24251. See Note [Case-to-let for strictly-used binders] in GHC.Core.Opt.Simplify.Iteration, plus #24251, for lots of discussion. Final Nofib changes over 0.1%: +----------------------------------------- | imaginary/digits-of-e2 -2.16% | imaginary/rfib -0.15% | real/fluid -0.10% | real/gamteb -1.47% | real/gg -0.20% | real/maillist +0.19% | real/pic -0.23% | real/scs -0.43% | shootout/n-body -0.41% | shootout/spectral-norm -0.12% +======================================== | geom mean -0.05% Pleasingly, overall executable size is down by just over 1%. Compile times (in perf/compiler) wobble around a bit +/- 0.5%, but the geometric mean is -0.1% which seems good. - - - - - a2a12054 by Simon Peyton Jones at 2024-02-01T09:34:39+00:00 Remove redunant bangs in GHC.Num.Integer There seems to be no good rationale for these bangs. - - - - - 10 changed files: - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - libraries/ghc-bignum/src/GHC/Num/Integer.hs - testsuite/tests/numeric/should_compile/T19641.stderr - testsuite/tests/simplCore/should_compile/T15631.hs - testsuite/tests/simplCore/should_compile/T15631.stdout - testsuite/tests/simplCore/should_compile/T20103.stderr - testsuite/tests/simplCore/should_compile/T22611.stderr - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/simplCore/should_compile/all.T Changes: ===================================== compiler/GHC/Core/Opt/Simplify/Iteration.hs ===================================== @@ -2827,30 +2827,73 @@ Note [Case-to-let for strictly-used binders] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If we have this: case of r { _ -> ..r.. } - -where 'r' is used strictly in (..r..), we can safely transform to +where 'r' is used strictly in (..r..), we /could/ safely transform to let r = in ...r... - -This is a Good Thing, because 'r' might be dead (if the body just -calls error), or might be used just once (in which case it can be -inlined); or we might be able to float the let-binding up or down. -E.g. #15631 has an example. - -Note that this can change the error behaviour. For example, we might -transform - case x of { _ -> error "bad" } - --> error "bad" -which is might be puzzling if 'x' currently lambda-bound, but later gets -let-bound to (error "good"). - -Nevertheless, the paper "A semantics for imprecise exceptions" allows -this transformation. If you want to fix the evaluation order, use -'pseq'. See #8900 for an example where the loss of this -transformation bit us in practice. - -See also Note [Empty case alternatives] in GHC.Core. - -Historical notes +As a special case, we have a plain `seq` like + case r of r1 { _ -> ...r1... } +where `r` is used strictly, we /could/ simply drop the `case` to get + ...r.... + +HOWEVER, there are some serious downsides to this transformation, so +GHC doesn't do it any longer (#24251): + +* Suppose the Simplifier sees + case x of y* { __DEFAULT -> + let z = case y of { __DEFAULT -> expr } in + z+1 } + The "y*" means "y is used strictly in its scope. Now we may: + - Eliminate the inner case because `y` is evaluated. + Now the demand-info on `y` is not right, because `y` is no longer used + strictly in its scope. But it is hard to spot that without doing a new + demand analysis. So there is a danger that we will subsequently: + - Eliminate the outer case because `y` is used strictly + Yikes! We can't eliminate both! + +* It introduces space leaks (#24251). Consider + go 0 where go x = x `seq` go (x + 1) + It is an infinite loop, true, but it should not leak space. Yet if we drop + the `seq`, it will. Another great example is #21741. + +* Dropping the outer `case can change the error behaviour. For example, + we might transform + case x of { _ -> error "bad" } --> error "bad" + which is might be puzzling if 'x' currently lambda-bound, but later gets + let-bound to (error "good"). Tht is OK accoring to the paper "A semantics for + imprecise exceptions", but see #8900 for an example where the loss of this + transformation bit us in practice. + +* If we have (case e of x -> f x), where `f` is strict, then it looks as if `x` + is strictly used, and we could soundly transform to + let x = e in f x + But if f's strictness info got worse (which can happen in in obscure cases; + see #21392) then we might have turned a non-thunk into a thunk! Bad. + +Lacking this "drop-strictly-used-seq" transformation means we can end up with +some redundant-looking evals. For example, consider + f x y = case x of DEFAULT -> -- A redundant-looking eval + case y of + True -> case x of { Nothing -> False; Just z -> z } + False -> case x of { Nothing -> True; Just z -> z } +That outer eval will be retained right through to code generation. But, +perhaps surprisingly, that is probably a /good/ thing: + + Key point: those inner (case x) expressions will be compiled a simple 'if', + because the code generator can see that `x` is, at those points, evaluated + and properly tagged. + +If we dropped the outer eval, both the inner (case x) expressions would need to +do a proper eval, pushing a return address, with an info table. See the example +in #15631 where, in the Description, the (case ys) will be a simple multi-way +jump. + +In fact (#24251), when I stopped GHC implementing the drop-strictly-used-seqs +transformation, binary sizes fell by 1%, and a few programs actually allocated +less and ran faster. A case in point is nofib/imaginary/digits-of-e2. (I'm not +sure exactly why it improves so much, though.) + +Slightly related: Note [Empty case alternatives] in GHC.Core. + +Historical notes: There have been various earlier versions of this patch: @@ -3124,8 +3167,9 @@ doCaseToLet scrut case_bndr | otherwise -- Scrut has a lifted type = exprIsHNF scrut - || isStrUsedDmd (idDemandInfo case_bndr) - -- See Note [Case-to-let for strictly-used binders] + -- || isStrUsedDmd (idDemandInfo case_bndr) + -- We no longer look at the demand on the case binder + -- See Note [Case-to-let for strictly-used binders] -------------------------------------------------- -- 3. Catch-all case ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -74,6 +74,7 @@ import GHC.Types.Demand import GHC.Types.Var.Set import GHC.Types.Basic +import GHC.Data.Maybe ( orElse ) import GHC.Data.OrdList ( isNilOL ) import GHC.Data.FastString ( fsLit ) @@ -2358,6 +2359,44 @@ the outer case scrutinises the same variable as the outer case. This transformation is called Case Merging. It avoids that the same variable is scrutinised multiple times. +Wrinkles + +(MC1) `tryCaseMerge` "looks though" an inner single-alternative case-on-variable. + For example + case x of { + ...outer-alts... + DEFAULT -> case y of (a,b) -> + case x of { A -> rhs1; B -> rhs2 } + ===> + case x of + ...outer-alts... + a -> case y of (a,b) -> rhs1 + B -> case y of (a,b) -> rhs2 + + This duplicates the `case y` but it removes the case x; so it is a win + in terms of execution time (combining the cases on x) at the cost of + perhaps duplicating the `case y`. A case in point is integerEq, which + is defined thus + integerEq :: Integer -> Integer -> Bool + integerEq !x !y = isTrue# (integerEq# x y) + which becomes + integerEq + = \ (x :: Integer) (y_aAL :: Integer) -> + case x of x1 { __DEFAULT -> + case y of y1 { __DEFAULT -> + case x1 of { + IS x2 -> case y1 of { + __DEFAULT -> GHC.Types.False; + IS y2 -> tagToEnum# @Bool (==# x2 y2) }; + IP x2 -> ... + IN x2 -> ... + We want to merge the outer `case x` with the inner `case x1`. + + This story is not fully robust; it will be defeated by a let-binding, + whih we don't want to duplicate. But accounting for single-alternative + case-on-variable is easy to do, and seems useful in common cases so + `tryMergeCase` does it. + Note [Eliminate Identity Case] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ case e of ===> e @@ -2537,24 +2576,25 @@ mkCase, mkCase1, mkCase2, mkCase3 -- 1. Merge Nested Cases -------------------------------------------------- -mkCase mode scrut outer_bndr alts_ty (Alt DEFAULT _ deflt_rhs : outer_alts) +mkCase mode scrut outer_bndr alts_ty alts | sm_case_merge mode - , (ticks, Case (Var inner_scrut_var) inner_bndr _ inner_alts) - <- stripTicksTop tickishFloatable deflt_rhs - , inner_scrut_var == outer_bndr + , Just alts' <- tryMergeCase outer_bndr alts = do { tick (CaseMerge outer_bndr) - - ; let wrap_alt (Alt con args rhs) = assert (outer_bndr `notElem` args) - (Alt con args (wrap_rhs rhs)) - -- Simplifier's no-shadowing invariant should ensure - -- that outer_bndr is not shadowed by the inner patterns - wrap_rhs rhs = Let (NonRec inner_bndr (Var outer_bndr)) rhs - -- The let is OK even for unboxed binders, - - wrapped_alts | isDeadBinder inner_bndr = inner_alts - | otherwise = map wrap_alt inner_alts - - merged_alts = mergeAlts outer_alts wrapped_alts + ; mkCase1 mode scrut outer_bndr alts_ty alts' } + -- Warning: don't call mkCase recursively! + -- Firstly, there's no point, because inner alts have already had + -- mkCase applied to them, so they won't have a case in their default + -- Secondly, if you do, you get an infinite loop, because the bindCaseBndr + -- in munge_rhs may put a case into the DEFAULT branch! + | otherwise + = mkCase1 mode scrut outer_bndr alts_ty alts + +tryMergeCase :: OutId -> [OutAlt] -> Maybe [OutAlt] +-- See Note [Merge Nested Cases] +tryMergeCase outer_bndr (Alt DEFAULT _ deflt_rhs : outer_alts) + = case go 5 (\e -> e) emptyVarSet deflt_rhs of + Nothing -> Nothing + Just inner_alts -> Just (mergeAlts outer_alts inner_alts) -- NB: mergeAlts gives priority to the left -- case x of -- A -> e1 @@ -2563,17 +2603,42 @@ mkCase mode scrut outer_bndr alts_ty (Alt DEFAULT _ deflt_rhs : outer_alts) -- B -> e3 -- When we merge, we must ensure that e1 takes -- precedence over e2 as the value for A! - - ; fmap (mkTicks ticks) $ - mkCase1 mode scrut outer_bndr alts_ty merged_alts - } - -- Warning: don't call mkCase recursively! - -- Firstly, there's no point, because inner alts have already had - -- mkCase applied to them, so they won't have a case in their default - -- Secondly, if you do, you get an infinite loop, because the bindCaseBndr - -- in munge_rhs may put a case into the DEFAULT branch! - -mkCase mode scrut bndr alts_ty alts = mkCase1 mode scrut bndr alts_ty alts + where + go :: Int -> (OutExpr -> OutExpr) -> VarSet -> OutExpr -> Maybe [OutAlt] + -- In the call (go wrap free_bndrs rhs), the `wrap` function has free `free_bndrs`; + -- so do not push `wrap` under any binders that would shadow `free_bndrs` + -- + -- The 'n' is just a depth-bound to avoid pathalogical quadratic behaviour with + -- case x1 of DEFAULT -> case x2 of DEFAULT -> case x3 of DEFAULT -> ... + -- when for each `case` we'll look down the whole chain to see if there is + -- another `case` on that same variable. Also all of these (case xi) evals + -- get duplicated in each branch of the outer case, so 'n' controls how much + -- duplication we are prepared to put up with. + go 0 _ _ _ = Nothing + + go n wrap free_bndrs (Tick t rhs) + = go n (wrap . Tick t) free_bndrs rhs + go _ wrap free_bndrs (Case (Var inner_scrut_var) inner_bndr _ inner_alts) + | inner_scrut_var == outer_bndr + , let wrap_let rhs' | isDeadBinder inner_bndr = rhs' + | otherwise = Let (NonRec inner_bndr (Var outer_bndr)) rhs' + -- The let is OK even for unboxed binders, + free_bndrs' = extendVarSet free_bndrs outer_bndr + = Just [ assert (not (any (`elemVarSet` free_bndrs') bndrs)) $ + Alt con bndrs (wrap (wrap_let rhs)) + | Alt con bndrs rhs <- inner_alts ] + go n wrap free_bndrs (Case (Var inner_scrut) inner_bndr ty inner_alts) + | [Alt con bndrs rhs] <- inner_alts -- Wrinkle (MC1) + , let wrap_case rhs' = Case (Var inner_scrut) inner_bndr ty $ + tryMergeCase inner_bndr alts `orElse` alts + where + alts = [Alt con bndrs rhs'] + = assert (not (outer_bndr `elem` (inner_bndr : bndrs))) $ + go (n-1) (wrap . wrap_case) (free_bndrs `extendVarSet` inner_scrut) rhs + + go _ _ _ _ = Nothing + +tryMergeCase _ _ = Nothing -------------------------------------------------- -- 2. Eliminate Identity Case ===================================== libraries/ghc-bignum/src/GHC/Num/Integer.hs ===================================== @@ -382,27 +382,27 @@ integerIsOne _ = False -- | Not-equal predicate. integerNe :: Integer -> Integer -> Bool -integerNe !x !y = isTrue# (integerNe# x y) +integerNe x y = isTrue# (integerNe# x y) -- | Equal predicate. integerEq :: Integer -> Integer -> Bool -integerEq !x !y = isTrue# (integerEq# x y) +integerEq x y = isTrue# (integerEq# x y) -- | Lower-or-equal predicate. integerLe :: Integer -> Integer -> Bool -integerLe !x !y = isTrue# (integerLe# x y) +integerLe x y = isTrue# (integerLe# x y) -- | Lower predicate. integerLt :: Integer -> Integer -> Bool -integerLt !x !y = isTrue# (integerLt# x y) +integerLt x y = isTrue# (integerLt# x y) -- | Greater predicate. integerGt :: Integer -> Integer -> Bool -integerGt !x !y = isTrue# (integerGt# x y) +integerGt x y = isTrue# (integerGt# x y) -- | Greater-or-equal predicate. integerGe :: Integer -> Integer -> Bool -integerGe !x !y = isTrue# (integerGe# x y) +integerGe x y = isTrue# (integerGe# x y) -- | Equal predicate. integerEq# :: Integer -> Integer -> Bool# ===================================== testsuite/tests/numeric/should_compile/T19641.stderr ===================================== @@ -6,7 +6,7 @@ Result size of Tidy Core natural_to_word = \ eta -> case eta of { - NS x1 -> Just (W# x1); + NS x2 -> Just (W# x2); NB ds -> Nothing } @@ -14,8 +14,8 @@ integer_to_int = \ eta -> case eta of { IS ipv -> Just (I# ipv); - IP x1 -> Nothing; - IN ds -> Nothing + IP x -> Nothing; + IN ds2 -> Nothing } ===================================== testsuite/tests/simplCore/should_compile/T15631.hs ===================================== @@ -7,5 +7,5 @@ f xs = let ys = reverse xs let w = length xs in w + length (reverse (case ys of { a:as -> as; [] -> [] })) - - +-- Feb 24: because of #24251 we now expect ys to be +-- evaluated early, and then case-analysed later ===================================== testsuite/tests/simplCore/should_compile/T15631.stdout ===================================== @@ -1,6 +1,7 @@ case GHC.List.$wlenAcc @a (Foo.f2 @a) 0# of v { __DEFAULT -> + case reverse @a xs of ys { __DEFAULT -> case GHC.List.$wlenAcc @a xs 0# of ww1 { __DEFAULT -> - case GHC.List.reverse1 @a xs (GHC.Types.[] @a) of { + case ys of { [] -> case Foo.f1 @a of { GHC.Types.I# v1 -> GHC.Prim.+# ww1 v1 }; case GHC.List.$wlenAcc case Foo.$wf @a xs of ww [Occ=Once1] { __DEFAULT -> ===================================== testsuite/tests/simplCore/should_compile/T20103.stderr ===================================== @@ -1,7 +1,12 @@ +T20103.hs:7:24: warning: [GHC-63394] [-Wx-partial (in -Wextended-warnings)] + In the use of ‘head’ + (imported from Prelude, but defined in GHC.List): + "This is a partial function, it throws an error on empty lists. Use pattern matching, 'Data.List.uncons' or 'Data.Maybe.listToMaybe' instead. Consider refactoring to use "Data.List.NonEmpty"." + ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 136, types: 88, coercions: 25, joins: 0/0} + = {terms: 139, types: 89, coercions: 22, joins: 0/0} -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} lvl :: Int @@ -31,8 +36,9 @@ lvl4 = GHC.CString.unpackCString# lvl3 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} T20103.$trModule2 :: GHC.Prim.Addr# [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 30 0}] T20103.$trModule2 = "T20103"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} @@ -43,8 +49,9 @@ lvl5 = GHC.CString.unpackCString# T20103.$trModule2 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} T20103.$trModule4 :: GHC.Prim.Addr# [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 20 0}] T20103.$trModule4 = "main"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} @@ -110,10 +117,10 @@ lvl16 :: CallStack ~R# (?callStack::CallStack))) Rec { --- RHS size: {terms: 44, types: 41, coercions: 21, joins: 0/0} +-- RHS size: {terms: 47, types: 42, coercions: 18, joins: 0/0} T20103.$wfoo [InlPrag=[2], Occ=LoopBreaker] :: HasCallStack => GHC.Prim.Int# -> GHC.Prim.Int# -[GblId[StrictWorker([!])], Arity=2, Str=<1L>, Unf=OtherCon []] +[GblId[StrictWorker([!])], Arity=2, Str=<1L><1L>, Unf=OtherCon []] T20103.$wfoo = \ ($dIP :: HasCallStack) (ww :: GHC.Prim.Int#) -> case ww of ds { @@ -136,28 +143,26 @@ T20103.$wfoo (GHC.Prim.-# ds 1#) }; 0# -> - case getCallStack - ($dIP - `cast` (GHC.Classes.N:IP[0] <"callStack">_N _N - :: (?callStack::CallStack) ~R# CallStack)) - of { + case $dIP + `cast` (GHC.Classes.N:IP[0] <"callStack">_N _N + :: (?callStack::CallStack) ~R# CallStack) + of wild1 + { __DEFAULT -> + case getCallStack wild1 of { [] -> - case $dIP - `cast` (GHC.Classes.N:IP[0] <"callStack">_N _N - :: (?callStack::CallStack) ~R# CallStack) - of wild1 { - __DEFAULT -> case lvl16 wild1 of wild2 { }; + case wild1 of wild2 { + __DEFAULT -> case lvl16 wild2 of {}; GHC.Stack.Types.FreezeCallStack ds1 -> case GHC.List.head1 @([Char], SrcLoc) - (wild1 + (wild2 `cast` (Sym (GHC.Classes.N:IP[0] <"callStack">_N _N) :: CallStack ~R# (?callStack::CallStack))) - of wild2 { - } + of {} }; : x ds1 -> case x of { (x1, ds2) -> GHC.List.$wlenAcc @Char x1 0# } } + } } end Rec } @@ -165,10 +170,10 @@ end Rec } foo [InlPrag=[2]] :: HasCallStack => Int -> Int [GblId, Arity=2, - Str=<1!P(1L)>, + Str=<1L><1!P(1L)>, Cpr=1, - Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, + Unf=Unf{Src=StableSystem, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False) Tmpl= \ ($dIP [Occ=Once1] :: HasCallStack) (eta [Occ=Once1!] :: Int) -> @@ -186,22 +191,25 @@ foo -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} T20103.$trModule3 :: GHC.Types.TrName [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 10 10}] T20103.$trModule3 = GHC.Types.TrNameS T20103.$trModule4 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} T20103.$trModule1 :: GHC.Types.TrName [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 10 10}] T20103.$trModule1 = GHC.Types.TrNameS T20103.$trModule2 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} T20103.$trModule :: GHC.Types.Module [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 10 10}] T20103.$trModule = GHC.Types.Module T20103.$trModule3 T20103.$trModule1 ===================================== testsuite/tests/simplCore/should_compile/T22611.stderr ===================================== @@ -1,7 +1,7 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 544, types: 486, coercions: 0, joins: 0/7} + = {terms: 562, types: 505, coercions: 0, joins: 0/10} $WFound = \ @a @m conrep conrep1 -> @@ -54,13 +54,14 @@ $w$sgo15 __DEFAULT -> let { hi1 = or# (uncheckedShiftRL# ww 1#) 9223372036854775808## } in - let { zeros = word2Int# (ctz# ds3) } in - (# Just ipv4, uncheckedShiftRL# hi1 zeros, + let { zeros = ctz# ds3 } in + let { zeros1 = word2Int# zeros } in + (# Just ipv4, uncheckedShiftRL# hi1 zeros1, or# (uncheckedShiftRL# (or# (uncheckedShiftRL# ds3 1#) (uncheckedShiftL# ww 63#)) - zeros) - (uncheckedShiftL# hi1 (-# 64# zeros)) #); + zeros1) + (uncheckedShiftL# hi1 (-# 64# zeros1)) #); 0## -> (# Just ipv4, 0##, uncheckedShiftRL# @@ -116,12 +117,13 @@ $w$sgo15 __DEFAULT -> let { hi1 = or# (uncheckedShiftRL# ww 1#) 9223372036854775808## } in - let { zeros = word2Int# (ctz# ds3) } in - (# Just ipv4, uncheckedShiftRL# hi1 zeros, + let { zeros = ctz# ds3 } in + let { zeros1 = word2Int# zeros } in + (# Just ipv4, uncheckedShiftRL# hi1 zeros1, or# (uncheckedShiftRL# - (or# (uncheckedShiftRL# ds3 1#) (uncheckedShiftL# ww 63#)) zeros) - (uncheckedShiftL# hi1 (-# 64# zeros)) #); + (or# (uncheckedShiftRL# ds3 1#) (uncheckedShiftL# ww 63#)) zeros1) + (uncheckedShiftL# hi1 (-# 64# zeros1)) #); 0## -> (# Just ipv4, 0##, uncheckedShiftRL# @@ -138,12 +140,13 @@ $w$sgo15 __DEFAULT -> let { hi1 = or# (uncheckedShiftRL# ww 1#) 9223372036854775808## } in - let { zeros = word2Int# (ctz# ds3) } in - (# Nothing, uncheckedShiftRL# hi1 zeros, + let { zeros = ctz# ds3 } in + let { zeros1 = word2Int# zeros } in + (# Nothing, uncheckedShiftRL# hi1 zeros1, or# (uncheckedShiftRL# - (or# (uncheckedShiftRL# ds3 1#) (uncheckedShiftL# ww 63#)) zeros) - (uncheckedShiftL# hi1 (-# 64# zeros)) #); + (or# (uncheckedShiftRL# ds3 1#) (uncheckedShiftL# ww 63#)) zeros1) + (uncheckedShiftL# hi1 (-# 64# zeros1)) #); 0## -> (# Nothing, 0##, uncheckedShiftRL# @@ -156,7 +159,8 @@ end Rec } $salterF = \ @v @a f1 k1 m -> - case $w$sgo15 9223372036854775808## 0## k1 m of + case k1 of k2 { __DEFAULT -> + case $w$sgo15 9223372036854775808## 0## k2 m of { (# ww, ww1, ww2 #) -> case f1 ww of { NotFound -> NotFound; @@ -167,18 +171,22 @@ $salterF Nothing -> case ww of { Nothing -> m; - Just old -> case $wbogus (##) of { __DEFAULT -> $wgo ww1 ww2 m } + Just old -> + case m of m1 { __DEFAULT -> + case $wbogus (##) of { __DEFAULT -> $wgo ww1 ww2 m1 } + } }; Just new -> case new of new1 { __DEFAULT -> case ww of { - Nothing -> $winsertAlong ww1 ww2 k1 new1 m; + Nothing -> $winsertAlong ww1 ww2 k2 new1 m; Just ds -> $wreplaceAlong ww1 ww2 new1 m } } }) } } + } lvl = \ @v ds -> @@ -190,10 +198,12 @@ lvl Rec { $wfoo = \ @v x subst -> - case $salterF lvl x subst of { + case x of x1 { __DEFAULT -> + case subst of subst1 { __DEFAULT -> + case $salterF lvl x1 subst1 of { NotFound -> - case x of wild1 { - Left x1 -> $wfoo wild1 subst; + case x1 of wild1 { + Left x2 -> $wfoo wild1 subst1; Right y -> $wfoo (Right @@ -204,10 +214,12 @@ $wfoo 1# -> C# (chr# i#) } })) - subst + subst1 }; Found p q -> (# p, q #) } + } + } end Rec } foo ===================================== testsuite/tests/simplCore/should_compile/T7360.stderr ===================================== @@ -1,15 +1,15 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 116, types: 50, coercions: 0, joins: 0/0} + = {terms: 119, types: 52, coercions: 0, joins: 0/0} -- RHS size: {terms: 6, types: 3, coercions: 0, joins: 0/0} T7360.$WFoo3 [InlPrag=INLINE[final] CONLIKE] :: Int %1 -> Foo [GblId[DataConWrapper], Arity=1, Str=, - Unf=Unf{Src=StableSystem, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, + Unf=Unf{Src=StableSystem, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) Tmpl= \ (conrep [Occ=Once1!] :: Int) -> case conrep of { GHC.Types.I# unbx [Occ=Once1] -> @@ -31,8 +31,8 @@ fun1 [InlPrag=NOINLINE[final]] :: Foo -> () Arity=1, Str=<1A>, Cpr=1, - Unf=Unf{Src=StableSystem, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, + Unf=Unf{Src=StableSystem, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) Tmpl= \ (x [Occ=Once1] :: Foo) -> case T7360.$wfun1 x of { (# #) -> GHC.Tuple.Prim.() }}] @@ -43,65 +43,75 @@ fun1 -- RHS size: {terms: 5, types: 1, coercions: 0, joins: 0/0} T7360.fun4 :: () [GblId, - Unf=Unf{Src=, TopLvl=True, Value=False, ConLike=False, - WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 30 10}] + Unf=Unf{Src=, TopLvl=True, + Value=False, ConLike=False, WorkFree=False, Expandable=False, + Guidance=IF_ARGS [] 30 10}] T7360.fun4 = case T7360.$wfun1 T7360.Foo1 of { (# #) -> GHC.Tuple.Prim.() } --- RHS size: {terms: 11, types: 7, coercions: 0, joins: 0/0} +-- RHS size: {terms: 14, types: 9, coercions: 0, joins: 0/0} fun2 :: forall {a}. [a] -> ((), Int) [GblId, Arity=1, Str=, Cpr=1, - Unf=Unf{Src=StableSystem, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, + Unf=Unf{Src=StableSystem, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) Tmpl= \ (@a) (x [Occ=Once1] :: [a]) -> (T7360.fun4, - case GHC.List.$wlenAcc @a x 0# of ww1 [Occ=Once1] { __DEFAULT -> + case x of wild [Occ=Once1] { __DEFAULT -> + case GHC.List.$wlenAcc @a wild 0# of ww1 [Occ=Once1] { __DEFAULT -> GHC.Types.I# ww1 + } })}] fun2 = \ (@a) (x :: [a]) -> (T7360.fun4, - case GHC.List.$wlenAcc @a x 0# of ww1 { __DEFAULT -> + case x of wild { __DEFAULT -> + case GHC.List.$wlenAcc @a wild 0# of ww1 { __DEFAULT -> GHC.Types.I# ww1 + } }) -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} T7360.$trModule4 :: GHC.Prim.Addr# [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 20 0}] T7360.$trModule4 = "main"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} T7360.$trModule3 :: GHC.Types.TrName [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 10 10}] T7360.$trModule3 = GHC.Types.TrNameS T7360.$trModule4 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} T7360.$trModule2 :: GHC.Prim.Addr# [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 30 0}] T7360.$trModule2 = "T7360"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} T7360.$trModule1 :: GHC.Types.TrName [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 10 10}] T7360.$trModule1 = GHC.Types.TrNameS T7360.$trModule2 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} T7360.$trModule :: GHC.Types.Module [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 10 10}] T7360.$trModule = GHC.Types.Module T7360.$trModule3 T7360.$trModule1 @@ -115,22 +125,25 @@ $krep -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} T7360.$tcFoo2 :: GHC.Prim.Addr# [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 20 0}] T7360.$tcFoo2 = "Foo"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} T7360.$tcFoo1 :: GHC.Types.TrName [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 10 10}] T7360.$tcFoo1 = GHC.Types.TrNameS T7360.$tcFoo2 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0} T7360.$tcFoo :: GHC.Types.TyCon [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 10 10}] T7360.$tcFoo = GHC.Types.TyCon 1581370841583180512#Word64 @@ -150,22 +163,25 @@ T7360.$tc'Foo4 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} T7360.$tc'Foo6 :: GHC.Prim.Addr# [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 30 0}] T7360.$tc'Foo6 = "'Foo1"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} T7360.$tc'Foo5 :: GHC.Types.TrName [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 10 10}] T7360.$tc'Foo5 = GHC.Types.TrNameS T7360.$tc'Foo6 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0} T7360.$tc'Foo1 :: GHC.Types.TyCon [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 10 10}] T7360.$tc'Foo1 = GHC.Types.TyCon 3986951253261644518#Word64 @@ -178,22 +194,25 @@ T7360.$tc'Foo1 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} T7360.$tc'Foo8 :: GHC.Prim.Addr# [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 30 0}] T7360.$tc'Foo8 = "'Foo2"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} T7360.$tc'Foo7 :: GHC.Types.TrName [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 10 10}] T7360.$tc'Foo7 = GHC.Types.TrNameS T7360.$tc'Foo8 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0} T7360.$tc'Foo2 :: GHC.Types.TyCon [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 10 10}] T7360.$tc'Foo2 = GHC.Types.TyCon 17325079864060690428#Word64 @@ -211,22 +230,25 @@ T7360.$tc'Foo9 = GHC.Types.KindRepFun $krep T7360.$tc'Foo4 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} T7360.$tc'Foo11 :: GHC.Prim.Addr# [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 30 0}] T7360.$tc'Foo11 = "'Foo3"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} T7360.$tc'Foo10 :: GHC.Types.TrName [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 10 10}] T7360.$tc'Foo10 = GHC.Types.TrNameS T7360.$tc'Foo11 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0} T7360.$tc'Foo3 :: GHC.Types.TyCon [GblId, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] + Unf=Unf{Src=, TopLvl=True, + Value=True, ConLike=True, WorkFree=True, Expandable=True, + Guidance=IF_ARGS [] 10 10}] T7360.$tc'Foo3 = GHC.Types.TyCon 3674231676522181654#Word64 ===================================== testsuite/tests/simplCore/should_compile/all.T ===================================== @@ -417,8 +417,10 @@ test('T21391', normal, compile, ['-O -dcore-lint']) # T22112: Simply test that dumping the Core doesn't loop becuse of the unfolding and ignore the dump output test('T22112', [ grep_errmsg('never matches') ], compile, ['-O -dsuppress-uniques -dno-typeable-binds -fexpose-all-unfoldings -ddump-simpl']) test('T21391a', normal, compile, ['-O -dcore-lint']) + # We don't want to see a thunk allocation for the insertBy expression after CorePrep. -test('T21392', [ grep_errmsg(r'sat.* :: \[\(.*Unique, .*Int\)\]'), expect_broken(21392) ], compile, ['-O -ddump-prep -dno-typeable-binds -dsuppress-uniques']) +test('T21392', [ grep_errmsg(r'sat.* :: \[\(.*Unique, .*Int\)\]') ], compile, ['-O -ddump-prep -dno-typeable-binds -dsuppress-uniques']) + test('T21689', [extra_files(['T21689a.hs'])], multimod_compile, ['T21689', '-v0 -O']) test('T21801', normal, compile, ['-O -dcore-lint']) test('T21848', [grep_errmsg(r'SPEC wombat') ], compile, ['-O -ddump-spec']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2ed26e0bf273516a33cea934976f20009e05c63e...a2a12054bb0aaaa9a78f71bf08e3a7ae3c0bde5a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2ed26e0bf273516a33cea934976f20009e05c63e...a2a12054bb0aaaa9a78f71bf08e3a7ae3c0bde5a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 10:49:43 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 01 Feb 2024 05:49:43 -0500 Subject: [Git][ghc/ghc][master] Make decomposeRuleLhs a bit more clever Message-ID: <65bb774783113_12c9d311d3cc81497@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: ca2e919e by Simon Peyton Jones at 2024-01-31T09:29:45+00:00 Make decomposeRuleLhs a bit more clever This fixes #24370 by making decomposeRuleLhs undertand dictionary /functions/ as well as plain /dictionaries/ - - - - - 5 changed files: - compiler/GHC.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/HsToCore/Binds.hs - + testsuite/tests/simplCore/should_compile/T24370.hs - testsuite/tests/simplCore/should_compile/all.T Changes: ===================================== compiler/GHC.hs ===================================== @@ -1515,9 +1515,7 @@ modInfoModBreaks :: ModuleInfo -> ModBreaks modInfoModBreaks = minf_modBreaks isDictonaryId :: Id -> Bool -isDictonaryId id - = case tcSplitSigmaTy (idType id) of { - (_tvs, _theta, tau) -> isDictTy tau } +isDictonaryId id = isDictTy (idType id) -- | Looks up a global name: that is, any top-level name in any -- visible module. Unlike 'lookupName', lookupGlobalName does not use ===================================== compiler/GHC/Core/Predicate.hs ===================================== @@ -99,7 +99,14 @@ mkClassPred :: Class -> [Type] -> PredType mkClassPred clas tys = mkTyConApp (classTyCon clas) tys isDictTy :: Type -> Bool -isDictTy = isClassPred +-- True of dictionaries (Eq a) and +-- dictionary functions (forall a. Eq a => Eq [a]) +-- See Note [Type determines value] +-- See #24370 (and the isDictId call in GHC.HsToCore.Binds.decomposeRuleLhs) +-- for why it's important to catch dictionary bindings +isDictTy ty = isClassPred pred + where + (_, pred) = splitInvisPiTys ty typeDeterminesValue :: Type -> Bool -- See Note [Type determines value] ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -987,7 +987,16 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs = Left (DsRuleIgnoredDueToConstructor con) -- See Note [No RULES on datacons] | otherwise = case decompose fun2 args2 of - Nothing -> Left (DsRuleLhsTooComplicated orig_lhs lhs2) + Nothing -> -- pprTrace "decomposeRuleLhs 3" (vcat [ text "orig_bndrs:" <+> ppr orig_bndrs + -- , text "orig_lhs:" <+> ppr orig_lhs + -- , text "rhs_fvs:" <+> ppr rhs_fvs + -- , text "orig_lhs:" <+> ppr orig_lhs + -- , text "lhs1:" <+> ppr lhs1 + -- , text "lhs2:" <+> ppr lhs2 + -- , text "fun2:" <+> ppr fun2 + -- , text "args2:" <+> ppr args2 + -- ]) $ + Left (DsRuleLhsTooComplicated orig_lhs lhs2) Just (fn_id, args) | not (null unbound) -> -- Check for things unbound on LHS @@ -1059,7 +1068,9 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs split_lets :: CoreExpr -> ([(DictId,CoreExpr)], CoreExpr) split_lets (Let (NonRec d r) body) - | isDictId d + | isDictId d -- Catches dictionaries, yes, but also catches dictionary + -- /functions/ arising from solving a + -- quantified contraint (#24370) = ((d,r):bs, body') where (bs, body') = split_lets body ===================================== testsuite/tests/simplCore/should_compile/T24370.hs ===================================== @@ -0,0 +1,16 @@ +{-# LANGUAGE QuantifiedConstraints, UndecidableInstances #-} + +-- This gave "RULE left-hand side too complicated to desugar" +-- in GHC 9.8 + +module T24370 where + +f :: (Eq a, Eq a) => a -> b -> Int +f = error "urk" + +{-# SPECIALISE f :: T Maybe -> b -> Int #-} + +instance (forall a. Eq a => Eq (f a)) => Eq (T f) where + a == b = False + +data T f = MkT (f Int) ===================================== testsuite/tests/simplCore/should_compile/all.T ===================================== @@ -511,3 +511,4 @@ test('T21917', normal, compile, ['-O -fkeep-auto-rules -ddump-rules']) test('T23209', [extra_files(['T23209_Aux.hs'])], multimod_compile, ['T23209', '-v0 -O']) test('T24229a', [ grep_errmsg(r'wfoo') ], compile, ['-O2 -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques -dppr-cols=99999']) test('T24229b', [ grep_errmsg(r'wfoo') ], compile, ['-O2 -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques -dppr-cols=99999']) +test('T24370', normal, compile, ['-O']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ca2e919ecca35db412e772d7eadd6a7c4fb20e4b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ca2e919ecca35db412e772d7eadd6a7c4fb20e4b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 10:50:39 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 01 Feb 2024 05:50:39 -0500 Subject: [Git][ghc/ghc][master] doc: Add -Dn flag to user guide Message-ID: <65bb777f430d9_12c9d33d7158858a8@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 94ce031d by Teo Camarasu at 2024-02-01T05:49:49-05:00 doc: Add -Dn flag to user guide Resolves #24394 - - - - - 1 changed file: - docs/users_guide/runtime_control.rst Changes: ===================================== docs/users_guide/runtime_control.rst ===================================== @@ -1408,6 +1408,7 @@ recommended for everyday use! .. rts-flag:: -Dl DEBUG: linker .. rts-flag:: -DL DEBUG: linker (verbose); implies :rts-flag:`-Dl` .. rts-flag:: -Dm DEBUG: stm +.. rts-flag:: -Dn DEBUG: non-moving garbage collector .. rts-flag:: -Dz DEBUG: stack squeezing .. rts-flag:: -Dc DEBUG: program coverage .. rts-flag:: -Dr DEBUG: sparks View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/94ce031ddc84ee702c12a11793028ef21e65fa00 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/94ce031ddc84ee702c12a11793028ef21e65fa00 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 11:21:40 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 01 Feb 2024 06:21:40 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 22 commits: doc: Add -Dn flag to user guide Message-ID: <65bb7ec49c914_12c9d45fc0689755@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 94ce031d by Teo Camarasu at 2024-02-01T05:49:49-05:00 doc: Add -Dn flag to user guide Resolves #24394 - - - - - 8eda4c0e by Ben Gamari at 2024-02-01T06:20:57-05:00 cmm: Introduce MO_RelaxedRead In hand-written Cmm it can sometimes be necessary to atomically load from memory deep within an expression (e.g. see the `CHECK_GC` macro). This MachOp provides a convenient way to do so without breaking the expression into multiple statements. - - - - - ec3b96b0 by Ben Gamari at 2024-02-01T06:20:57-05:00 codeGen: Use relaxed accesses in ticky bumping - - - - - bc075dcb by Ben Gamari at 2024-02-01T06:20:57-05:00 base: use atomic write when updating timer manager - - - - - ecbfaec7 by Ben Gamari at 2024-02-01T06:20:57-05:00 Use relaxed atomics to manipulate TSO status fields - - - - - bf2f54de by Ben Gamari at 2024-02-01T06:20:57-05:00 rts: Add necessary barriers when manipulating TSO owner - - - - - 89867656 by Ben Gamari at 2024-02-01T06:20:57-05:00 rts: Use `switch` to branch on why_blocked This is a semantics-preserving refactoring. - - - - - 70d143aa by Ben Gamari at 2024-02-01T06:20:57-05:00 rts: Fix synchronization on thread blocking state We now use a release barrier whenever we update a thread's blocking state. This required widening StgTSO.why_blocked as AArch64 does not support atomic writes on 16-bit values. - - - - - 5cc16749 by Ben Gamari at 2024-02-01T06:20:57-05:00 rts: Fix data race in threadPaused This only affects an assertion in the debug RTS and only needs relaxed ordering. - - - - - 05e67624 by Ben Gamari at 2024-02-01T06:20:57-05:00 rts: Fix data race in threadStatus# - - - - - 47bc1baa by Ben Gamari at 2024-02-01T06:20:57-05:00 rts: Fix data race in Interpreter's preemption check - - - - - be16da15 by Ben Gamari at 2024-02-01T06:20:57-05:00 rts/Messages: Fix data race - - - - - e996e3e1 by Ben Gamari at 2024-02-01T06:20:57-05:00 rts/Prof: Fix data race - - - - - ffac1bd0 by Ben Gamari at 2024-02-01T06:20:57-05:00 rts: Use relaxed ordering on dirty/clean info tables updates When changing the dirty/clean state of a mutable object we needn't have any particular ordering. - - - - - e99c6b0b by Ben Gamari at 2024-02-01T06:20:57-05:00 codeGen: Use relaxed-read in closureInfoPtr - - - - - daf3bfd6 by Ben Gamari at 2024-02-01T06:20:57-05:00 STM: Use acquire loads when possible Full sequential consistency is not needed here. - - - - - ccf99ab7 by Ben Gamari at 2024-02-01T06:20:57-05:00 rts: Use fence rather than redundant load Previously we would use an atomic load to ensure acquire ordering. However, we now have `ACQUIRE_FENCE_ON`, which allows us to express this more directly. - - - - - b65fccf4 by Ben Gamari at 2024-02-01T06:20:57-05:00 rts: Fix data races in profiling timer - - - - - 75dbdede by Ben Gamari at 2024-02-01T06:20:57-05:00 Add Note [C11 memory model] - - - - - 9c08244e by Ben Gamari at 2024-02-01T06:20:58-05:00 Add os-string as a boot package Introduces `os-string` submodule. This will be necessary for `filepath-1.5`. - - - - - 74e0fdc2 by Ben Gamari at 2024-02-01T06:20:58-05:00 Bump filepath to 1.5.0.0 Required bumps of the following submodules: * `directory` * `filepath` * `haskeline` * `process` * `unix` * `hsc2hs` * `Win32` * `semaphore-compat` and the addition of `os-string` as a boot package. - - - - - 94f757e9 by Andrei Borzenkov at 2024-02-01T06:20:58-05:00 Namespacing for WARNING/DEPRECATED pragmas (#24396) New syntax for WARNING and DEPRECATED pragmas was added, namely namespace specifierss: namespace_spec ::= 'type' | 'data' | {- empty -} warning ::= warning_category namespace_spec namelist strings deprecation ::= namespace_spec namelist strings A new data type was introduced to represent these namespace specifiers: data NamespaceSpecifier = NoSpecifier | TypeNamespaceSpecifier (EpToken "type") | DataNamespaceSpecifier (EpToken "data") Extension field XWarning now contains this NamespaceSpecifier. lookupBindGroupOcc function was changed: it now takes NamespaceSpecifier and checks that the namespace of the found names matches the passed flag. With this change {-# WARNING data D "..." #-} pragma will only affect value namespace and {-# WARNING type D "..." #-} will only affect type namespace. The same logic is applicable to DEPRECATED pragmas. Finding duplicated warnings inside rnSrcWarnDecls now takes into consideration NamespaceSpecifier flag to allow warnings with the same names that refer to different namespaces. - - - - - 30 changed files: - .gitmodules - compiler/GHC/Cmm/Expr.hs - compiler/GHC/Cmm/Info.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/ghc.cabal.in - docs/users_guide/9.10.1-notes.rst - docs/users_guide/exts/pragmas.rst - docs/users_guide/runtime_control.rst - ghc/ghc-bin.cabal.in - hadrian/src/Packages.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Packages.hs - libraries/Cabal - libraries/Win32 - libraries/base/src/GHC/Event/Thread.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/64b252d2c907f8ff8541b879598be5a5385a41b3...94f757e9d84e119427f4c5cf6a7461a4df84bfd9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/64b252d2c907f8ff8541b879598be5a5385a41b3...94f757e9d84e119427f4c5cf6a7461a4df84bfd9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 12:40:31 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Thu, 01 Feb 2024 07:40:31 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/no-reg-lists Message-ID: <65bb913f1dd8c_12c9d68f077c1109aa@gitlab.mail> Ben Gamari pushed new branch wip/no-reg-lists at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/no-reg-lists You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 12:40:40 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Thu, 01 Feb 2024 07:40:40 -0500 Subject: [Git][ghc/ghc][wip/no-reg-lists] hi Message-ID: <65bb914832b2d_12c9d690ccec11117@gitlab.mail> Spam detection software, running on the system "mail.haskell.org", has identified this incoming email as possible spam. The original message has been attached to this so you can view it (if it isn't spam) or label similar future email. If you have any questions, see @@CONTACT_ADDRESS@@ for details. Content preview: Ben Gamari pushed to branch wip/no-reg-lists at Glasgow Haskell Compiler / GHC Commits: 3166c554 by Ben Gamari at 2024-02-01T07:40:31-05:00 hi - - - - - [...] Content analysis details: (5.1 points, 5.0 required) pts rule name description ---- ---------------------- -------------------------------------------------- -0.0 SPF_HELO_PASS SPF: HELO matches SPF record -0.0 T_RP_MATCHES_RCVD Envelope sender domain matches handover relay domain -0.0 SPF_PASS SPF: sender matches SPF record 0.9 FRT_ADOBE2 BODY: ReplaceTags: Adobe 1.1 URI_HEX URI: URI hostname has long hexadecimal sequence 5.0 UNWANTED_LANGUAGE_BODY BODY: Message written in an undesired language -1.9 BAYES_00 BODY: Bayes spam probability is 0 to 1% [score: 0.0000] 0.0 HTML_MESSAGE BODY: HTML included in message 0.0 T_DKIM_INVALID DKIM-Signature header exists but is not valid The original message was not completely plain text, and may be unsafe to open with some email clients; in particular, it may contain a virus, or confirm that your address can receive spam. If you wish to view it, it may be safer to save it to a file and open it with an editor. -------------- next part -------------- An embedded message was scrubbed... From: "Ben Gamari (@bgamari)" Subject: [Git][ghc/ghc][wip/no-reg-lists] hi Date: Thu, 01 Feb 2024 07:40:40 -0500 Size: 498871 URL: From gitlab at gitlab.haskell.org Thu Feb 1 13:36:32 2024 From: gitlab at gitlab.haskell.org (Teo Camarasu (@teo)) Date: Thu, 01 Feb 2024 08:36:32 -0500 Subject: [Git][ghc/ghc][wip/T23397] rts: use live words to estimate heap size Message-ID: <65bb9e604ee2e_12c9d843f708129168@gitlab.mail> Teo Camarasu pushed to branch wip/T23397 at Glasgow Haskell Compiler / GHC Commits: 3e52b5df by Teo Camarasu at 2024-02-01T13:36:16+00:00 rts: use live words to estimate heap size We use live words rather than live blocks to determine the size of the heap for determining memory retention. Most of the time these two metrics align, but they can come apart in normal usage when using the nonmoving collector. The nonmoving collector leads to a lot of partially occupied blocks. So, using live words is more accurate. They can also come apart when the heap is suffering from high levels fragmentation caused by small pinned objects, but in this case, the block size is the more accurate metric. Since this case is best avoided anyway. It is ok to accept the trade-off that we might try (and probably) fail to return more memory in this case. See also the Note [Statistics for retaining memory] Resolves #23397 - - - - - 5 changed files: - docs/users_guide/9.10.1-notes.rst - rts/sm/GC.c - rts/sm/Storage.c - rts/sm/Storage.h - + testsuite/tests/rts/T23397.hs Changes: ===================================== docs/users_guide/9.10.1-notes.rst ===================================== @@ -140,6 +140,11 @@ Runtime system See :ghc-ticket:`23340`. :rts-flag:`--nonmoving-dense-allocator-count=⟨count⟩` has been added to fine-tune this behaviour. +- Memory return logic now uses live bytes rather than live blocks to measure the size of the heap. + This primarily affects the non-moving GC, which should now be more willing to return memory to the OS. + Users who have fine-tuned the :rts-flag:`-F ⟨factor⟩`, :rts-flag:`-Fd ⟨factor⟩`, or :rts-flag:`-O ⟨size⟩` flags, + and use the non-moving GC, should see if adjustments are needed in light of this change. + - Add a :rts-flag:`--no-automatic-time-samples` flag which stops time profiling samples being automatically started on startup. Time profiling can be controlled manually using functions in ``GHC.Profiling``. ===================================== rts/sm/GC.c ===================================== @@ -1002,10 +1002,15 @@ GarbageCollect (struct GcConfig config, need_copied_live = 0; need_uncopied_live = 0; for (i = 0; i < RtsFlags.GcFlags.generations; i++) { - need_copied_live += genLiveCopiedBlocks(&generations[i]); - need_uncopied_live += genLiveUncopiedBlocks(&generations[i]); + need_copied_live += genLiveCopiedWords(&generations[i]); + need_uncopied_live += genLiveUncopiedWords(&generations[i]); } + // Convert the live words into live blocks + // See Note [Statistics for retaining memory] + need_copied_live = BLOCK_ROUND_UP(need_copied_live) / BLOCK_SIZE_W; + need_uncopied_live = BLOCK_ROUND_UP(need_uncopied_live) / BLOCK_SIZE_W; + debugTrace(DEBUG_gc, "(before) copied_live: %d; uncopied_live: %d", need_copied_live, need_uncopied_live ); @@ -1029,7 +1034,7 @@ GarbageCollect (struct GcConfig config, ASSERT(need_uncopied_live + need_copied_live >= RtsFlags.GcFlags.minOldGenSize ); - debugTrace(DEBUG_gc, "(after) copyied_live: %d; uncopied_live: %d", need_copied_live, need_uncopied_live ); + debugTrace(DEBUG_gc, "(after) copied_live: %d; uncopied_live: %d", need_copied_live, need_uncopied_live ); need_prealloc = 0; for (i = 0; i < n_nurseries; i++) { @@ -1067,7 +1072,7 @@ GarbageCollect (struct GcConfig config, W_ scaled_needed = ((scaled_factor + unavoidable_copied_need_factor) * need_copied_live) + ((scaled_factor + unavoidable_uncopied_need_factor) * need_uncopied_live); - debugTrace(DEBUG_gc, "factors_2: %f %d", ((scaled_factor + unavoidable_copied_need_factor) * need_copied_live), ((scaled_factor + unavoidable_uncopied_need_factor) * need_uncopied_live)); + debugTrace(DEBUG_gc, "factors_2: %f %f", ((scaled_factor + unavoidable_copied_need_factor) * need_copied_live), ((scaled_factor + unavoidable_uncopied_need_factor) * need_uncopied_live)); need = need_prealloc + scaled_needed; /* Also, if user set heap size, do not drop below it. @@ -2422,3 +2427,39 @@ bool doIdleGCWork(Capability *cap STG_UNUSED, bool all) * */ + +/* Note [Statistics for retaining memory] +* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +* +* At the end of GC, we want to determine the size of the heap in order to +* determine the amount of memory we wish to return to the OS, or if we want +* to increase the heap size to the minimum. +* +* There's two promising candidates for this metric: live words, and live blocks. +* +* Measuring live blocks is promising because blocks are the smallest unit +* that the storage manager can (de)allocate. +* Most of the time live words and live blocks are very similar. +* +* But the two metrics can come apart when the heap is dominated +* by small pinned objects, or when using the non-moving collector. +* +* In both cases, this happens because objects cannot be copied, so +* block occupancy can fall as objects in a block become garbage. +* In situations like this, using live blocks to determine memory +* retention behaviour can lead to us being overly conservative. +* +* Instead we use live words rounded up to the block size to measure +* heap size. This gives us a more accurate picture of the heap. +* +* This works particularly well with the nonmoving collector as we +* can reuse the space taken up by dead heap objects. This choice is less good +* for fragmentation caused by a few pinned objects retaining blocks. +* In that case, the block can only be reused if it is deallocated in its entirety. +* And therefore using live blocks would be more accurate in this case. +* We assume that this is relatively rare and when it does happen, +* this fragmentation is a problem that should be addressed in its own right. +* +* See: #23397 +* +*/ ===================================== rts/sm/Storage.c ===================================== @@ -1642,11 +1642,36 @@ W_ countOccupied (bdescr *bd) return words; } -// Returns the total number of live blocks +// Returns the total number of live words W_ genLiveWords (generation *gen) { - return (gen->live_estimate ? gen->live_estimate : gen->n_words) + - gen->n_large_words + gen->n_compact_blocks * BLOCK_SIZE_W; + return genLiveCopiedWords(gen) + genLiveUncopiedWords(gen); +} + +// The number of live words which will be copied by the copying collector. +W_ genLiveCopiedWords (generation *gen) +{ + if (gen == oldest_gen && RtsFlags.GcFlags.useNonmoving){ + // the non-moving generation doesn't contain any copied data + return 0; + } else { + return gen->live_estimate ? gen->live_estimate : gen->n_words; + } +} + +// The number of live words which will not be copied by the copying collector +// This includes data living in non-moving collector segments, compact blocks and large/pinned blocks. +W_ genLiveUncopiedWords(generation *gen) +{ + W_ nonmoving_blocks = 0; + // The nonmoving heap contains some blocks that live outside the regular generation structure. + if (gen == oldest_gen && RtsFlags.GcFlags.useNonmoving){ + nonmoving_blocks = + (gen->live_estimate ? gen->live_estimate : gen->n_words) + + nonmoving_large_words + + nonmoving_compact_words; + } + return gen->n_large_words + gen->n_compact_blocks * BLOCK_SIZE_W + nonmoving_blocks; } // The number of live blocks which will be copied by the copying collector. ===================================== rts/sm/Storage.h ===================================== @@ -111,6 +111,8 @@ StgWord gcThreadLiveWords (uint32_t i, uint32_t g); StgWord gcThreadLiveBlocks (uint32_t i, uint32_t g); StgWord genLiveWords (generation *gen); +StgWord genLiveCopiedWords (generation *gen); +StgWord genLiveUncopiedWords (generation *gen); StgWord genLiveBlocks (generation *gen); StgWord genLiveCopiedBlocks (generation *gen); StgWord genLiveUncopiedBlocks (generation *gen); ===================================== testsuite/tests/rts/T23397.hs ===================================== @@ -0,0 +1,79 @@ +{-# LANGUAGE MagicHash, UnboxedTuples, NumericUnderscores, ForeignFunctionInterface #-} + +module Main where + +import GHC.Exts +import GHC.IO +import System.Mem +import System.Environment +import Debug.Trace +import Control.Monad +import GHC.Stats +import Data.Word +import GHC.Stack (HasCallStack) +import Control.DeepSeq + +foreign import ccall "performBlockingMajorGC" performBlockingMajorGC :: IO () + +-- Ensure that when using the non-moving collector that +-- our memory return behaviour reflects the amount of live data, not the live blocks. +-- The nature of the non-moving collector means that often we have lots of unused live blocks +-- that surpass the live data. +-- So, going off live blocks would mean we hold onto too much memory. +-- +-- In this test, we create a situation where live data is a small subset of live blocks. +-- Then we allocate some data into the oldest generation to increase its size and then +-- examine how much memory is returned when it is freed. +-- +-- In order to make this easier to reproduce in a test we use a high -F value +main :: IO () +main = do + [sn] <- getArgs + let n = read sn + -- create a list of Integers and promote it to the oldest gen + xs <- evaluate $ force $ [0..(n :: Integer)] + performBlockingMajorGC + performBlockingMajorGC + let + prune (x:xs) = x:prune (drop 1000 xs) + prune [] = [] + -- now delete most of it. This should make the heap like swiss cheese + xs' <- evaluate $ force $ prune xs + performBlockingMajorGC + performBlockingMajorGC + -- allocate a bunch + xss <- traverse newByteArray $ replicate (fromIntegral n * 8) 60 + performBlockingMajorGC + performBlockingMajorGC + evaluate xss + -- and free it + performBlockingMajorGC + performBlockingMajorGC + performBlockingMajorGC + evaluate xs' + stats <- getRTSStats + performBlockingMajorGC + performBlockingMajorGC + -- now let's check that our megablock usage is reflective of our live data + stats' <- getRTSStats + let live = fromIntegral . gcdetails_live_bytes $ gc stats + let penultimate_mem_usage = fromIntegral . gcdetails_mem_in_use_bytes $ gc stats + let ultimate_mem_usage = fromIntegral . gcdetails_mem_in_use_bytes $ gc stats' + let mem_usage = penultimate_mem_usage - ultimate_mem_usage -- discount memory that we can't free + let scale = 8 + 1.2 + + -- print live + -- print $ floor penultimate_mem_usage + -- print $ floor mem_usage + -- print $ live * scale + unless (live * scale < mem_usage) $ + error $ "expected " ++ show live ++ " bytes memory used but got " ++ show mem_usage ++ " instead" + + pure () + +data BA = BA ByteArray# + +newByteArray :: Int -> IO BA +newByteArray (I# sz#) = IO $ \s -> case newByteArray# sz# s of + (# s', k #) -> case unsafeFreezeByteArray# k s' of + (# s'', ba# #) -> (# s'', BA ba# #) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3e52b5df7c9b9e7f5ced5c79b9f59b66c905c3bd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3e52b5df7c9b9e7f5ced5c79b9f59b66c905c3bd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 13:37:17 2024 From: gitlab at gitlab.haskell.org (Teo Camarasu (@teo)) Date: Thu, 01 Feb 2024 08:37:17 -0500 Subject: [Git][ghc/ghc][wip/T23397] rts: use live words to estimate heap size Message-ID: <65bb9e8db3d46_12c9d8531850129924@gitlab.mail> Teo Camarasu pushed to branch wip/T23397 at Glasgow Haskell Compiler / GHC Commits: 35ef8dc8 by Teo Camarasu at 2024-02-01T13:37:08+00:00 rts: use live words to estimate heap size We use live words rather than live blocks to determine the size of the heap for determining memory retention. Most of the time these two metrics align, but they can come apart in normal usage when using the nonmoving collector. The nonmoving collector leads to a lot of partially occupied blocks. So, using live words is more accurate. They can also come apart when the heap is suffering from high levels fragmentation caused by small pinned objects, but in this case, the block size is the more accurate metric. Since this case is best avoided anyway. It is ok to accept the trade-off that we might try (and probably) fail to return more memory in this case. See also the Note [Statistics for retaining memory] Resolves #23397 - - - - - 4 changed files: - docs/users_guide/9.10.1-notes.rst - rts/sm/GC.c - rts/sm/Storage.c - rts/sm/Storage.h Changes: ===================================== docs/users_guide/9.10.1-notes.rst ===================================== @@ -140,6 +140,11 @@ Runtime system See :ghc-ticket:`23340`. :rts-flag:`--nonmoving-dense-allocator-count=⟨count⟩` has been added to fine-tune this behaviour. +- Memory return logic now uses live bytes rather than live blocks to measure the size of the heap. + This primarily affects the non-moving GC, which should now be more willing to return memory to the OS. + Users who have fine-tuned the :rts-flag:`-F ⟨factor⟩`, :rts-flag:`-Fd ⟨factor⟩`, or :rts-flag:`-O ⟨size⟩` flags, + and use the non-moving GC, should see if adjustments are needed in light of this change. + - Add a :rts-flag:`--no-automatic-time-samples` flag which stops time profiling samples being automatically started on startup. Time profiling can be controlled manually using functions in ``GHC.Profiling``. ===================================== rts/sm/GC.c ===================================== @@ -1002,10 +1002,15 @@ GarbageCollect (struct GcConfig config, need_copied_live = 0; need_uncopied_live = 0; for (i = 0; i < RtsFlags.GcFlags.generations; i++) { - need_copied_live += genLiveCopiedBlocks(&generations[i]); - need_uncopied_live += genLiveUncopiedBlocks(&generations[i]); + need_copied_live += genLiveCopiedWords(&generations[i]); + need_uncopied_live += genLiveUncopiedWords(&generations[i]); } + // Convert the live words into live blocks + // See Note [Statistics for retaining memory] + need_copied_live = BLOCK_ROUND_UP(need_copied_live) / BLOCK_SIZE_W; + need_uncopied_live = BLOCK_ROUND_UP(need_uncopied_live) / BLOCK_SIZE_W; + debugTrace(DEBUG_gc, "(before) copied_live: %d; uncopied_live: %d", need_copied_live, need_uncopied_live ); @@ -1029,7 +1034,7 @@ GarbageCollect (struct GcConfig config, ASSERT(need_uncopied_live + need_copied_live >= RtsFlags.GcFlags.minOldGenSize ); - debugTrace(DEBUG_gc, "(after) copyied_live: %d; uncopied_live: %d", need_copied_live, need_uncopied_live ); + debugTrace(DEBUG_gc, "(after) copied_live: %d; uncopied_live: %d", need_copied_live, need_uncopied_live ); need_prealloc = 0; for (i = 0; i < n_nurseries; i++) { @@ -1067,7 +1072,7 @@ GarbageCollect (struct GcConfig config, W_ scaled_needed = ((scaled_factor + unavoidable_copied_need_factor) * need_copied_live) + ((scaled_factor + unavoidable_uncopied_need_factor) * need_uncopied_live); - debugTrace(DEBUG_gc, "factors_2: %f %d", ((scaled_factor + unavoidable_copied_need_factor) * need_copied_live), ((scaled_factor + unavoidable_uncopied_need_factor) * need_uncopied_live)); + debugTrace(DEBUG_gc, "factors_2: %f %f", ((scaled_factor + unavoidable_copied_need_factor) * need_copied_live), ((scaled_factor + unavoidable_uncopied_need_factor) * need_uncopied_live)); need = need_prealloc + scaled_needed; /* Also, if user set heap size, do not drop below it. @@ -2422,3 +2427,39 @@ bool doIdleGCWork(Capability *cap STG_UNUSED, bool all) * */ + +/* Note [Statistics for retaining memory] +* ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +* +* At the end of GC, we want to determine the size of the heap in order to +* determine the amount of memory we wish to return to the OS, or if we want +* to increase the heap size to the minimum. +* +* There's two promising candidates for this metric: live words, and live blocks. +* +* Measuring live blocks is promising because blocks are the smallest unit +* that the storage manager can (de)allocate. +* Most of the time live words and live blocks are very similar. +* +* But the two metrics can come apart when the heap is dominated +* by small pinned objects, or when using the non-moving collector. +* +* In both cases, this happens because objects cannot be copied, so +* block occupancy can fall as objects in a block become garbage. +* In situations like this, using live blocks to determine memory +* retention behaviour can lead to us being overly conservative. +* +* Instead we use live words rounded up to the block size to measure +* heap size. This gives us a more accurate picture of the heap. +* +* This works particularly well with the nonmoving collector as we +* can reuse the space taken up by dead heap objects. This choice is less good +* for fragmentation caused by a few pinned objects retaining blocks. +* In that case, the block can only be reused if it is deallocated in its entirety. +* And therefore using live blocks would be more accurate in this case. +* We assume that this is relatively rare and when it does happen, +* this fragmentation is a problem that should be addressed in its own right. +* +* See: #23397 +* +*/ ===================================== rts/sm/Storage.c ===================================== @@ -1642,11 +1642,36 @@ W_ countOccupied (bdescr *bd) return words; } -// Returns the total number of live blocks +// Returns the total number of live words W_ genLiveWords (generation *gen) { - return (gen->live_estimate ? gen->live_estimate : gen->n_words) + - gen->n_large_words + gen->n_compact_blocks * BLOCK_SIZE_W; + return genLiveCopiedWords(gen) + genLiveUncopiedWords(gen); +} + +// The number of live words which will be copied by the copying collector. +W_ genLiveCopiedWords (generation *gen) +{ + if (gen == oldest_gen && RtsFlags.GcFlags.useNonmoving){ + // the non-moving generation doesn't contain any copied data + return 0; + } else { + return gen->live_estimate ? gen->live_estimate : gen->n_words; + } +} + +// The number of live words which will not be copied by the copying collector +// This includes data living in non-moving collector segments, compact blocks and large/pinned blocks. +W_ genLiveUncopiedWords(generation *gen) +{ + W_ nonmoving_blocks = 0; + // The nonmoving heap contains some blocks that live outside the regular generation structure. + if (gen == oldest_gen && RtsFlags.GcFlags.useNonmoving){ + nonmoving_blocks = + (gen->live_estimate ? gen->live_estimate : gen->n_words) + + nonmoving_large_words + + nonmoving_compact_words; + } + return gen->n_large_words + gen->n_compact_blocks * BLOCK_SIZE_W + nonmoving_blocks; } // The number of live blocks which will be copied by the copying collector. ===================================== rts/sm/Storage.h ===================================== @@ -111,6 +111,8 @@ StgWord gcThreadLiveWords (uint32_t i, uint32_t g); StgWord gcThreadLiveBlocks (uint32_t i, uint32_t g); StgWord genLiveWords (generation *gen); +StgWord genLiveCopiedWords (generation *gen); +StgWord genLiveUncopiedWords (generation *gen); StgWord genLiveBlocks (generation *gen); StgWord genLiveCopiedBlocks (generation *gen); StgWord genLiveUncopiedBlocks (generation *gen); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/35ef8dc83428f5405e092b12eb8cfc440b6504d8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/35ef8dc83428f5405e092b12eb8cfc440b6504d8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 13:39:37 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Thu, 01 Feb 2024 08:39:37 -0500 Subject: [Git][ghc/ghc][wip/filepath-1.5] 4 commits: Make decomposeRuleLhs a bit more clever Message-ID: <65bb9f197cbea_12c9d8609a841307bc@gitlab.mail> Zubin pushed to branch wip/filepath-1.5 at Glasgow Haskell Compiler / GHC Commits: ca2e919e by Simon Peyton Jones at 2024-01-31T09:29:45+00:00 Make decomposeRuleLhs a bit more clever This fixes #24370 by making decomposeRuleLhs undertand dictionary /functions/ as well as plain /dictionaries/ - - - - - 94ce031d by Teo Camarasu at 2024-02-01T05:49:49-05:00 doc: Add -Dn flag to user guide Resolves #24394 - - - - - 8a47c243 by Ben Gamari at 2024-02-01T13:39:33+00:00 Add os-string as a boot package Introduces `os-string` submodule. This will be necessary for `filepath-1.5`. - - - - - d1139dff by Ben Gamari at 2024-02-01T13:39:33+00:00 Bump filepath to 1.5.0.0 Required bumps of the following submodules: * `directory` * `filepath` * `haskeline` * `process` * `unix` * `hsc2hs` * `Win32` * `semaphore-compat` and the addition of `os-string` as a boot package. - - - - - 22 changed files: - .gitmodules - compiler/GHC.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/HsToCore/Binds.hs - compiler/ghc.cabal.in - docs/users_guide/runtime_control.rst - ghc/ghc-bin.cabal.in - hadrian/src/Packages.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Packages.hs - libraries/Cabal - libraries/Win32 - libraries/directory - libraries/filepath - libraries/ghc-boot/ghc-boot.cabal.in - libraries/ghci/ghci.cabal.in - + libraries/os-string - libraries/process - libraries/semaphore-compat - libraries/unix - + testsuite/tests/simplCore/should_compile/T24370.hs - testsuite/tests/simplCore/should_compile/all.T Changes: ===================================== .gitmodules ===================================== @@ -117,3 +117,6 @@ [submodule "utils/hpc"] path = utils/hpc url = https://gitlab.haskell.org/hpc/hpc-bin.git +[submodule "libraries/os-string"] + path = libraries/os-string + url = https://gitlab.haskell.org/ghc/packages/os-string ===================================== compiler/GHC.hs ===================================== @@ -1515,9 +1515,7 @@ modInfoModBreaks :: ModuleInfo -> ModBreaks modInfoModBreaks = minf_modBreaks isDictonaryId :: Id -> Bool -isDictonaryId id - = case tcSplitSigmaTy (idType id) of { - (_tvs, _theta, tau) -> isDictTy tau } +isDictonaryId id = isDictTy (idType id) -- | Looks up a global name: that is, any top-level name in any -- visible module. Unlike 'lookupName', lookupGlobalName does not use ===================================== compiler/GHC/Core/Predicate.hs ===================================== @@ -99,7 +99,14 @@ mkClassPred :: Class -> [Type] -> PredType mkClassPred clas tys = mkTyConApp (classTyCon clas) tys isDictTy :: Type -> Bool -isDictTy = isClassPred +-- True of dictionaries (Eq a) and +-- dictionary functions (forall a. Eq a => Eq [a]) +-- See Note [Type determines value] +-- See #24370 (and the isDictId call in GHC.HsToCore.Binds.decomposeRuleLhs) +-- for why it's important to catch dictionary bindings +isDictTy ty = isClassPred pred + where + (_, pred) = splitInvisPiTys ty typeDeterminesValue :: Type -> Bool -- See Note [Type determines value] ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -987,7 +987,16 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs = Left (DsRuleIgnoredDueToConstructor con) -- See Note [No RULES on datacons] | otherwise = case decompose fun2 args2 of - Nothing -> Left (DsRuleLhsTooComplicated orig_lhs lhs2) + Nothing -> -- pprTrace "decomposeRuleLhs 3" (vcat [ text "orig_bndrs:" <+> ppr orig_bndrs + -- , text "orig_lhs:" <+> ppr orig_lhs + -- , text "rhs_fvs:" <+> ppr rhs_fvs + -- , text "orig_lhs:" <+> ppr orig_lhs + -- , text "lhs1:" <+> ppr lhs1 + -- , text "lhs2:" <+> ppr lhs2 + -- , text "fun2:" <+> ppr fun2 + -- , text "args2:" <+> ppr args2 + -- ]) $ + Left (DsRuleLhsTooComplicated orig_lhs lhs2) Just (fn_id, args) | not (null unbound) -> -- Check for things unbound on LHS @@ -1059,7 +1068,9 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs split_lets :: CoreExpr -> ([(DictId,CoreExpr)], CoreExpr) split_lets (Let (NonRec d r) body) - | isDictId d + | isDictId d -- Catches dictionaries, yes, but also catches dictionary + -- /functions/ arising from solving a + -- quantified contraint (#24370) = ((d,r):bs, body') where (bs, body') = split_lets body ===================================== compiler/ghc.cabal.in ===================================== @@ -116,7 +116,7 @@ Library time >= 1.4 && < 1.13, containers >= 0.6.2.1 && < 0.8, array >= 0.1 && < 0.6, - filepath >= 1 && < 1.5, + filepath >= 1 && < 1.6, template-haskell == 2.21.*, hpc >= 0.6 && < 0.8, transformers >= 0.5 && < 0.7, @@ -128,7 +128,7 @@ Library ghci == @ProjectVersionMunged@ if os(windows) - Build-Depends: Win32 >= 2.3 && < 2.14 + Build-Depends: Win32 >= 2.3 && < 2.15 else Build-Depends: unix >= 2.7 && < 2.9 ===================================== docs/users_guide/runtime_control.rst ===================================== @@ -1408,6 +1408,7 @@ recommended for everyday use! .. rts-flag:: -Dl DEBUG: linker .. rts-flag:: -DL DEBUG: linker (verbose); implies :rts-flag:`-Dl` .. rts-flag:: -Dm DEBUG: stm +.. rts-flag:: -Dn DEBUG: non-moving garbage collector .. rts-flag:: -Dz DEBUG: stack squeezing .. rts-flag:: -Dc DEBUG: program coverage .. rts-flag:: -Dr DEBUG: sparks ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -36,14 +36,14 @@ Executable ghc bytestring >= 0.9 && < 0.13, directory >= 1 && < 1.4, process >= 1 && < 1.7, - filepath >= 1 && < 1.5, + filepath >= 1 && < 1.6, containers >= 0.5 && < 0.8, transformers >= 0.5 && < 0.7, ghc-boot == @ProjectVersionMunged@, ghc == @ProjectVersionMunged@ if os(windows) - Build-Depends: Win32 >= 2.3 && < 2.14 + Build-Depends: Win32 >= 2.3 && < 2.15 else Build-Depends: unix >= 2.7 && < 2.9 ===================================== hadrian/src/Packages.hs ===================================== @@ -8,7 +8,7 @@ module Packages ( ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghcInternal, ghci, ghciWrapper, ghcPkg, ghcPrim, ghcToolchain, ghcToolchainBin, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, iservProxy, - libffi, mtl, parsec, pretty, primitive, process, remoteIserv, rts, + libffi, mtl, osString, parsec, pretty, primitive, process, remoteIserv, rts, runGhc, semaphoreCompat, stm, templateHaskell, terminfo, text, time, timeout, touchy, transformers, unlit, unix, win32, xhtml, lintersCommon, lintNotes, lintCodes, lintCommitMsg, lintSubmoduleRefs, lintWhitespace, @@ -40,7 +40,7 @@ ghcPackages = , exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcPlatform , ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghcInternal, ghci, ghciWrapper, ghcPkg, ghcPrim , ghcToolchain, ghcToolchainBin, haddock, haskeline, hsc2hs - , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, libffi, mtl + , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, libffi, mtl, osString , parsec, pretty, process, rts, runGhc, stm, semaphoreCompat, templateHaskell , terminfo, text, time, touchy, transformers, unlit, unix, win32, xhtml , timeout @@ -58,7 +58,7 @@ array, base, binary, bytestring, cabalSyntax, cabal, checkPpr, checkExact, count ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghci, ghcInternal, ghciWrapper, ghcPkg, ghcPrim, ghcToolchain, ghcToolchainBin, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, iservProxy, remoteIserv, libffi, mtl, - parsec, pretty, primitive, process, rts, runGhc, semaphoreCompat, stm, templateHaskell, + osString, parsec, pretty, primitive, process, rts, runGhc, semaphoreCompat, stm, templateHaskell, terminfo, text, time, touchy, transformers, unlit, unix, win32, xhtml, timeout, lintersCommon, lintNotes, lintCodes, lintCommitMsg, lintSubmoduleRefs, lintWhitespace @@ -112,6 +112,7 @@ iserv = util "iserv" iservProxy = util "iserv-proxy" libffi = top "libffi" mtl = lib "mtl" +osString = lib "os-string" parsec = lib "parsec" pretty = lib "pretty" primitive = lib "primitive" ===================================== hadrian/src/Settings/Default.hs ===================================== @@ -104,6 +104,7 @@ stage0Packages = do , hpc , hpcBin , mtl + , osString , parsec , semaphoreCompat , time ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -157,6 +157,10 @@ packageArgs = do ] + , package unix ? builder (Cabal Flags) ? arg "+os-string" + , package directory ? builder (Cabal Flags) ? arg "+os-string" + , package win32 ? builder (Cabal Flags) ? arg "+os-string" + --------------------------------- iserv -------------------------------- -- Add -Wl,--export-dynamic enables GHCi to load dynamic objects that -- refer to the RTS. This is harmless if you don't use it (adds a bit ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit ae3c40a20bf98870488e3b40fc4495009b026e33 +Subproject commit ec71ed5b44d7a35e3b421c0d3f1f9f52cc434992 ===================================== libraries/Win32 ===================================== @@ -1 +1 @@ -Subproject commit efab7f1146da9741dc54fb35476d4aaabeff8d6d +Subproject commit 350ebd43f9a8d9e1ca767b0000f95bdfb42a5471 ===================================== libraries/directory ===================================== @@ -1 +1 @@ -Subproject commit a0c9361817db13917df7777f669a97c4d787f44e +Subproject commit fc38cbfc5c7c4b631ed89d6b41bbe00ee96c8b21 ===================================== libraries/filepath ===================================== @@ -1 +1 @@ -Subproject commit cdb5171f7774569b1a8028a78392cfa79f732b5c +Subproject commit b55465e3d174ccd63914e7146079435503204187 ===================================== libraries/ghc-boot/ghc-boot.cabal.in ===================================== @@ -78,7 +78,7 @@ Library bytestring >= 0.10 && < 0.13, containers >= 0.5 && < 0.8, directory >= 1.2 && < 1.4, - filepath >= 1.3 && < 1.5, + filepath >= 1.3 && < 1.6, deepseq >= 1.4 && < 1.6, ghc-platform >= 0.1, ghc-boot-th == @ProjectVersionMunged@ ===================================== libraries/ghci/ghci.cabal.in ===================================== @@ -81,7 +81,7 @@ library bytestring >= 0.10 && < 0.13, containers >= 0.5 && < 0.8, deepseq >= 1.4 && < 1.6, - filepath == 1.4.*, + filepath >= 1.4 && < 1.6, ghc-boot == @ProjectVersionMunged@, ghc-heap == @ProjectVersionMunged@, template-haskell == 2.21.*, ===================================== libraries/os-string ===================================== @@ -0,0 +1 @@ +Subproject commit fb2711ba1f43fd609de0e231e161025ee8ed3216 ===================================== libraries/process ===================================== @@ -1 +1 @@ -Subproject commit 5ba847afd894b560b7a7c2569c99bb9f4c8cb282 +Subproject commit dfdae0a7036b42d352a515214e6116424dd08ec9 ===================================== libraries/semaphore-compat ===================================== @@ -1 +1 @@ -Subproject commit c8fc7b1757b4eecbd10239038fbc6602340105b1 +Subproject commit 8cd32a85388c7b51786a7aedd15404e2e4896f1b ===================================== libraries/unix ===================================== @@ -1 +1 @@ -Subproject commit 0b3dbc9901fdf2d752c4ee7a7cee7b1ed20e76bd +Subproject commit 7db23ecad7593210ce38c48a462be6c50d080e00 ===================================== testsuite/tests/simplCore/should_compile/T24370.hs ===================================== @@ -0,0 +1,16 @@ +{-# LANGUAGE QuantifiedConstraints, UndecidableInstances #-} + +-- This gave "RULE left-hand side too complicated to desugar" +-- in GHC 9.8 + +module T24370 where + +f :: (Eq a, Eq a) => a -> b -> Int +f = error "urk" + +{-# SPECIALISE f :: T Maybe -> b -> Int #-} + +instance (forall a. Eq a => Eq (f a)) => Eq (T f) where + a == b = False + +data T f = MkT (f Int) ===================================== testsuite/tests/simplCore/should_compile/all.T ===================================== @@ -511,3 +511,4 @@ test('T21917', normal, compile, ['-O -fkeep-auto-rules -ddump-rules']) test('T23209', [extra_files(['T23209_Aux.hs'])], multimod_compile, ['T23209', '-v0 -O']) test('T24229a', [ grep_errmsg(r'wfoo') ], compile, ['-O2 -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques -dppr-cols=99999']) test('T24229b', [ grep_errmsg(r'wfoo') ], compile, ['-O2 -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques -dppr-cols=99999']) +test('T24370', normal, compile, ['-O']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cbb52840545ef4f9066a1c8db247f866f4f5b132...d1139dff003adcdbfbc9137c1816022f1ecd59ea -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cbb52840545ef4f9066a1c8db247f866f4f5b132...d1139dff003adcdbfbc9137c1816022f1ecd59ea You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 14:01:33 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 01 Feb 2024 09:01:33 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 23 commits: cmm: Introduce MO_RelaxedRead Message-ID: <65bba43d7806e_1ad4f29bd2c810301f@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 12639b18 by Ben Gamari at 2024-02-01T09:01:18-05:00 cmm: Introduce MO_RelaxedRead In hand-written Cmm it can sometimes be necessary to atomically load from memory deep within an expression (e.g. see the `CHECK_GC` macro). This MachOp provides a convenient way to do so without breaking the expression into multiple statements. - - - - - 38d74a3f by Ben Gamari at 2024-02-01T09:01:18-05:00 codeGen: Use relaxed accesses in ticky bumping - - - - - 73f5c8ff by Ben Gamari at 2024-02-01T09:01:18-05:00 base: use atomic write when updating timer manager - - - - - 9cdad4ba by Ben Gamari at 2024-02-01T09:01:18-05:00 Use relaxed atomics to manipulate TSO status fields - - - - - 727af8ad by Ben Gamari at 2024-02-01T09:01:18-05:00 rts: Add necessary barriers when manipulating TSO owner - - - - - 6f41f894 by Ben Gamari at 2024-02-01T09:01:18-05:00 rts: Use `switch` to branch on why_blocked This is a semantics-preserving refactoring. - - - - - 0ddc4632 by Ben Gamari at 2024-02-01T09:01:18-05:00 rts: Fix synchronization on thread blocking state We now use a release barrier whenever we update a thread's blocking state. This required widening StgTSO.why_blocked as AArch64 does not support atomic writes on 16-bit values. - - - - - 5a7ce400 by Ben Gamari at 2024-02-01T09:01:18-05:00 rts: Fix data race in threadPaused This only affects an assertion in the debug RTS and only needs relaxed ordering. - - - - - 8d6e9805 by Ben Gamari at 2024-02-01T09:01:18-05:00 rts: Fix data race in threadStatus# - - - - - 2b4a6ecf by Ben Gamari at 2024-02-01T09:01:18-05:00 rts: Fix data race in Interpreter's preemption check - - - - - 03735c3d by Ben Gamari at 2024-02-01T09:01:18-05:00 rts/Messages: Fix data race - - - - - 24aac350 by Ben Gamari at 2024-02-01T09:01:18-05:00 rts/Prof: Fix data race - - - - - 2cf25783 by Ben Gamari at 2024-02-01T09:01:18-05:00 rts: Use relaxed ordering on dirty/clean info tables updates When changing the dirty/clean state of a mutable object we needn't have any particular ordering. - - - - - 5fe52ca4 by Ben Gamari at 2024-02-01T09:01:18-05:00 codeGen: Use relaxed-read in closureInfoPtr - - - - - 52bb91b2 by Ben Gamari at 2024-02-01T09:01:18-05:00 STM: Use acquire loads when possible Full sequential consistency is not needed here. - - - - - 84be463e by Ben Gamari at 2024-02-01T09:01:18-05:00 rts: Use fence rather than redundant load Previously we would use an atomic load to ensure acquire ordering. However, we now have `ACQUIRE_FENCE_ON`, which allows us to express this more directly. - - - - - 9340021b by Ben Gamari at 2024-02-01T09:01:18-05:00 rts: Fix data races in profiling timer - - - - - 7aaf922a by Ben Gamari at 2024-02-01T09:01:18-05:00 Add Note [C11 memory model] - - - - - 87b4e48c by Cheng Shao at 2024-02-01T09:01:21-05:00 compiler: move generic cmm optimization logic in NCG to a standalone module This commit moves GHC.CmmToAsm.cmmToCmm to a standalone module, GHC.Cmm.GenericOpt. The main motivation is enabling this logic to be run in the wasm backend NCG code, which is defined in other modules that's imported by GHC.CmmToAsm, causing a cyclic dependency issue. - - - - - d4e89f35 by Cheng Shao at 2024-02-01T09:01:21-05:00 compiler: explicitly disable PIC in wasm32 NCG This commit explicitly disables the ncgPIC flag for the wasm32 target. The wasm backend doesn't support PIC for the time being. - - - - - d3980393 by Cheng Shao at 2024-02-01T09:01:21-05:00 compiler: enable generic cmm optimizations in wasm backend NCG This commit enables the generic cmm optimizations in other NCGs to be run in the wasm backend as well, followed by a late cmm control-flow optimization pass. The added optimizations do catch some corner cases not handled by the pre-NCG cmm pipeline and are useful in generating smaller CFGs. - - - - - 716b5e4d by Andrei Borzenkov at 2024-02-01T09:01:22-05:00 Namespacing for WARNING/DEPRECATED pragmas (#24396) New syntax for WARNING and DEPRECATED pragmas was added, namely namespace specifierss: namespace_spec ::= 'type' | 'data' | {- empty -} warning ::= warning_category namespace_spec namelist strings deprecation ::= namespace_spec namelist strings A new data type was introduced to represent these namespace specifiers: data NamespaceSpecifier = NoSpecifier | TypeNamespaceSpecifier (EpToken "type") | DataNamespaceSpecifier (EpToken "data") Extension field XWarning now contains this NamespaceSpecifier. lookupBindGroupOcc function was changed: it now takes NamespaceSpecifier and checks that the namespace of the found names matches the passed flag. With this change {-# WARNING data D "..." #-} pragma will only affect value namespace and {-# WARNING type D "..." #-} will only affect type namespace. The same logic is applicable to DEPRECATED pragmas. Finding duplicated warnings inside rnSrcWarnDecls now takes into consideration NamespaceSpecifier flag to allow warnings with the same names that refer to different namespaces. - - - - - f835c1b5 by Bryan Richter at 2024-02-01T09:01:22-05:00 CI: Disable the test-cabal-reinstall job Fixes #24363 - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/Cmm/Expr.hs - + compiler/GHC/Cmm/GenericOpt.hs - compiler/GHC/Cmm/Info.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Wasm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Driver/Config/CmmToAsm.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/ghc.cabal.in - docs/users_guide/9.10.1-notes.rst - docs/users_guide/exts/pragmas.rst - libraries/base/src/GHC/Event/Thread.hs - libraries/ghc-prim/GHC/Tuple.hs - rts/Exception.cmm - rts/HeapStackCheck.cmm The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/94f757e9d84e119427f4c5cf6a7461a4df84bfd9...f835c1b5bc7ada80ed7fd933514dbc893a78ab74 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/94f757e9d84e119427f4c5cf6a7461a4df84bfd9...f835c1b5bc7ada80ed7fd933514dbc893a78ab74 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 14:23:50 2024 From: gitlab at gitlab.haskell.org (Matthew Craven (@clyring)) Date: Thu, 01 Feb 2024 09:23:50 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/mkConstrTag-since Message-ID: <65bba976ffda_1ad4f21072410115661@gitlab.mail> Matthew Craven pushed new branch wip/mkConstrTag-since at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/mkConstrTag-since You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 14:30:55 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 01 Feb 2024 09:30:55 -0500 Subject: [Git][ghc/ghc][wip/bump-images-9.6] 16 commits: Fix #24308 Message-ID: <65bbab1f45d40_1ad4f218ecbf4117472@gitlab.mail> Matthew Pickering pushed to branch wip/bump-images-9.6 at Glasgow Haskell Compiler / GHC Commits: b2d8cd85 by Matt Walker at 2024-01-26T09:50:08-05:00 Fix #24308 Add tests for semicolon separated where clauses - - - - - 0da490a1 by Ben Gamari at 2024-01-26T17:34:41-05:00 hsc2hs: Bump submodule - - - - - 3f442fd2 by Ben Gamari at 2024-01-26T17:34:41-05:00 Bump containers submodule to 0.7 - - - - - 82a1c656 by Sebastian Nagel at 2024-01-29T02:32:40-05:00 base: with{Binary}File{Blocking} only annotates own exceptions Fixes #20886 This ensures that inner, unrelated exceptions are not misleadingly annotated with the opened file. - - - - - 9294a086 by Andreas Klebinger at 2024-01-29T02:33:15-05:00 Fix fma warning when using llvm on aarch64. On aarch64 fma is always on so the +fma flag doesn't exist for that target. Hence no need to try and pass +fma to llvm. Fixes #24379 - - - - - ced2e731 by sheaf at 2024-01-29T17:27:12-05:00 No shadowing warnings for NoFieldSelector fields This commit ensures we don't emit shadowing warnings when a user shadows a field defined with NoFieldSelectors. Fixes #24381 - - - - - 8eeadfad by Patrick at 2024-01-29T17:27:51-05:00 Fix bug wrong span of nested_doc_comment #24378 close #24378 1. Update the start position of span in `nested_doc_comment` correctly. and hence the spans of identifiers of haddoc can be computed correctly. 2. add test `HaddockSpanIssueT24378`. - - - - - a557580f by Alexey Radkov at 2024-01-30T19:41:52-05:00 Fix irrelevant dodgy-foreign-imports warning on import f-pointers by value A test *сс018* is attached (not sure about the naming convention though). Note that without the fix, the test fails with the *dodgy-foreign-imports* warning passed to stderr. The warning disappears after the fix. GHC shouldn't warn on imports of natural function pointers from C by value (which is feasible with CApiFFI), such as ```haskell foreign import capi "cc018.h value f" f :: FunPtr (Int -> IO ()) ``` where ```c void (*f)(int); ``` See a related real-world use-case [here](https://gitlab.com/daniel-casanueva/pcre-light/-/merge_requests/17). There, GHC warns on import of C function pointer `pcre_free`. - - - - - ca99efaf by Alexey Radkov at 2024-01-30T19:41:53-05:00 Rename test cc018 -> T24034 - - - - - 88c38dd5 by Ben Gamari at 2024-01-30T19:42:28-05:00 rts/TraverseHeap.c: Ensure that PosixSource.h is included first - - - - - ca2e919e by Simon Peyton Jones at 2024-01-31T09:29:45+00:00 Make decomposeRuleLhs a bit more clever This fixes #24370 by making decomposeRuleLhs undertand dictionary /functions/ as well as plain /dictionaries/ - - - - - 94ce031d by Teo Camarasu at 2024-02-01T05:49:49-05:00 doc: Add -Dn flag to user guide Resolves #24394 - - - - - 4d4c60df by Matthew Pickering at 2024-02-01T14:30:46+00:00 Use specific clang assembler when compiling with -fllvm There are situations where LLVM will produce assembly which older gcc toolchains can't handle. For example on Deb10, it seems that LLVM >= 13 produces assembly which the default gcc doesn't support. A more robust solution in the long term is to require a specific LLVM compatible assembler when using -fllvm. - - - - - 31ff9ba9 by Matthew Pickering at 2024-02-01T14:30:46+00:00 Update CI images with LLVM 15, ghc-9.6.4 and cabal-install-3.10.2.0 - - - - - bf7268fd by Matthew Pickering at 2024-02-01T14:30:46+00:00 Update bootstrap plans for 9.4.8 and 9.6.4 - - - - - 24faed16 by Matthew Pickering at 2024-02-01T14:30:46+00:00 Add alpine 3_18 release job This is mainly experimental and future proofing to enable a smooth transition to newer alpine releases once 3_12 is too old. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - compiler/GHC.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Pipeline/Phases.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Rename/Utils.hs - compiler/GHC/Settings.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/ghc.cabal.in - configure.ac - distrib/configure.ac.in - docs/users_guide/9.10.1-notes.rst - docs/users_guide/phases.rst - docs/users_guide/runtime_control.rst - ghc/ghc-bin.cabal.in - hadrian/bindist/Makefile - hadrian/bindist/config.mk.in - hadrian/bootstrap/generate_bootstrap_plans - hadrian/bootstrap/plan-9_4_1.json - hadrian/bootstrap/plan-9_4_2.json - hadrian/bootstrap/plan-9_4_3.json The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3b7c4e96704ab7f57f0257c92214cddb9f3da458...24faed169859523cd6bad1241e45e5da5a3b4ab9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3b7c4e96704ab7f57f0257c92214cddb9f3da458...24faed169859523cd6bad1241e45e5da5a3b4ab9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 14:47:34 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Thu, 01 Feb 2024 09:47:34 -0500 Subject: [Git][ghc/ghc][wip/ghc-internals-move] Move `base` to `ghc-internal` Message-ID: <65bbaf0624904_1ad4f21d3bac01179c3@gitlab.mail> Ben Gamari pushed to branch wip/ghc-internals-move at Glasgow Haskell Compiler / GHC Commits: 4a71af59 by Ben Gamari at 2024-02-01T09:47:26-05:00 Move `base` to `ghc-internal` Here we move a good deal of the implementation of `base` into a new package, `ghc-internal` such that it can be evolved independently from the user-visible interfaces of `base`. While we want to isolate implementation from interfaces, naturally, we would like to avoid turning `base` into a mere set of module re-exports. However, this is a non-trivial undertaking for a variety of reasons: * `base` contains numerous known-key and wired-in things, requiring corresponding changes in the compiler * `base` contains a significant amount of C code and corresponding autoconf logic, which is very fragile and difficult to break apart * `base` has numerous import cycles, which are currently dealt with via carefully balanced `hs-boot` files * We must not break existing users To accomplish this migration, I tried the following approaches: * [Split-GHC.Base]: Break apart the GHC.Base knot to allow incremental migration of modules into ghc-internal: this knot is simply too intertwined to be easily pulled apart, especially given the rather tricky import cycles that it contains) * [Move-Core]: Moving the "core" connected component of base (roughly 150 modules) into ghc-internal. While the Haskell side of this seems tractable, the C dependencies are very subtle to break apart. * [Move-Incrementally]: 1. Move all of base into ghc-internal 2. Examine the module structure and begin moving obvious modules (e.g. leaves of the import graph) back into base 3. Examine the modules remaining in ghc-internal, refactor as necessary to facilitate further moves 4. Go to (2) iterate until the cost/benefit of further moves is insufficient to justify continuing 5. Rename the modules moved into ghc-internal to ensure that they don't overlap with those in base 6. For each module moved into ghc-internal, add a shim module to base with the declarations which should be exposed and any requisite Haddocks (thus guaranteeing that base will be insulated from changes in the export lists of modules in ghc-internal Here I am using the [Move-Incrementally] approach, which is empirically the least painful of the unpleasant options above Metric Decrease: haddock.Cabal haddock.base Metric Increase: MultiComponentModulesRecomp T16875 - - - - - 30 changed files: - .gitignore - compiler/GHC/Builtin/Names.hs - compiler/GHC/StgToJS/Rts/Rts.hs - compiler/GHC/Unit/Types.hs - configure.ac - libraries/base/base.cabal - libraries/base/src/Control/Applicative.hs - libraries/base/src/Control/Concurrent.hs - libraries/base/src/Data/Complex.hs - libraries/base/src/Data/Semigroup.hs - + libraries/base/src/Dummy.hs - libraries/base/src/System/CPUTime/Posix/Times.hsc - libraries/base/.authorspellings → libraries/ghc-internal/.authorspellings - libraries/base/.gitignore → libraries/ghc-internal/.gitignore - libraries/base/.hlint.yaml → libraries/ghc-internal/.hlint.yaml - libraries/ghc-internal/LICENSE - libraries/base/Setup.hs → libraries/ghc-internal/Setup.hs - libraries/base/aclocal.m4 → libraries/ghc-internal/aclocal.m4 - libraries/base/cbits/CastFloatWord.cmm → libraries/ghc-internal/cbits/CastFloatWord.cmm - libraries/base/cbits/DarwinUtils.c → libraries/ghc-internal/cbits/DarwinUtils.c - libraries/base/cbits/IOutils.c → libraries/ghc-internal/cbits/IOutils.c - libraries/base/cbits/PrelIOUtils.c → libraries/ghc-internal/cbits/PrelIOUtils.c - libraries/base/cbits/SetEnv.c → libraries/ghc-internal/cbits/SetEnv.c - libraries/base/cbits/StackCloningDecoding.cmm → libraries/ghc-internal/cbits/StackCloningDecoding.cmm - libraries/base/cbits/Win32Utils.c → libraries/ghc-internal/cbits/Win32Utils.c - libraries/base/cbits/consUtils.c → libraries/ghc-internal/cbits/consUtils.c - libraries/base/cbits/iconv.c → libraries/ghc-internal/cbits/iconv.c - libraries/base/cbits/inputReady.c → libraries/ghc-internal/cbits/inputReady.c - libraries/base/cbits/md5.c → libraries/ghc-internal/cbits/md5.c - libraries/base/cbits/primFloat.c → libraries/ghc-internal/cbits/primFloat.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4a71af5996162923ca7a6434f0a860c58f2cfc9f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4a71af5996162923ca7a6434f0a860c58f2cfc9f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 17:21:55 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 01 Feb 2024 12:21:55 -0500 Subject: [Git][ghc/ghc][master] 18 commits: cmm: Introduce MO_RelaxedRead Message-ID: <65bbd333e116b_1ad4f260efe101366b8@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 31553b11 by Ben Gamari at 2024-02-01T12:21:29-05:00 cmm: Introduce MO_RelaxedRead In hand-written Cmm it can sometimes be necessary to atomically load from memory deep within an expression (e.g. see the `CHECK_GC` macro). This MachOp provides a convenient way to do so without breaking the expression into multiple statements. - - - - - 0785cf81 by Ben Gamari at 2024-02-01T12:21:29-05:00 codeGen: Use relaxed accesses in ticky bumping - - - - - be423dda by Ben Gamari at 2024-02-01T12:21:29-05:00 base: use atomic write when updating timer manager - - - - - 8a310e35 by Ben Gamari at 2024-02-01T12:21:29-05:00 Use relaxed atomics to manipulate TSO status fields - - - - - d6809ee4 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Add necessary barriers when manipulating TSO owner - - - - - 39e3ac5d by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Use `switch` to branch on why_blocked This is a semantics-preserving refactoring. - - - - - 515eb33d by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix synchronization on thread blocking state We now use a release barrier whenever we update a thread's blocking state. This required widening StgTSO.why_blocked as AArch64 does not support atomic writes on 16-bit values. - - - - - eb38812e by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in threadPaused This only affects an assertion in the debug RTS and only needs relaxed ordering. - - - - - 26c48dd6 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in threadStatus# - - - - - 6af43ab4 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in Interpreter's preemption check - - - - - 9502ad3c by Ben Gamari at 2024-02-01T12:21:29-05:00 rts/Messages: Fix data race - - - - - 60802db5 by Ben Gamari at 2024-02-01T12:21:30-05:00 rts/Prof: Fix data race - - - - - ef8ccef5 by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Use relaxed ordering on dirty/clean info tables updates When changing the dirty/clean state of a mutable object we needn't have any particular ordering. - - - - - 76fe2b75 by Ben Gamari at 2024-02-01T12:21:30-05:00 codeGen: Use relaxed-read in closureInfoPtr - - - - - a6316eb4 by Ben Gamari at 2024-02-01T12:21:30-05:00 STM: Use acquire loads when possible Full sequential consistency is not needed here. - - - - - 6bddfd3d by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Use fence rather than redundant load Previously we would use an atomic load to ensure acquire ordering. However, we now have `ACQUIRE_FENCE_ON`, which allows us to express this more directly. - - - - - 55c65dbc by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Fix data races in profiling timer - - - - - 856b5e75 by Ben Gamari at 2024-02-01T12:21:30-05:00 Add Note [C11 memory model] - - - - - 30 changed files: - compiler/GHC/Cmm/Expr.hs - compiler/GHC/Cmm/Info.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - libraries/base/src/GHC/Event/Thread.hs - rts/Exception.cmm - rts/HeapStackCheck.cmm - rts/Interpreter.c - rts/Messages.c - rts/PrimOps.cmm - rts/Proftimer.c - rts/RaiseAsync.c - rts/STM.c - rts/Schedule.c - rts/StgMiscClosures.cmm - rts/StgStartup.cmm - rts/ThreadPaused.c - rts/Threads.c - rts/TraverseHeap.c - rts/include/Cmm.h - rts/include/rts/storage/ClosureMacros.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/94ce031ddc84ee702c12a11793028ef21e65fa00...856b5e7561719ffce74595fca096082996163431 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/94ce031ddc84ee702c12a11793028ef21e65fa00...856b5e7561719ffce74595fca096082996163431 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 17:22:37 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 01 Feb 2024 12:22:37 -0500 Subject: [Git][ghc/ghc][master] 3 commits: compiler: move generic cmm optimization logic in NCG to a standalone module Message-ID: <65bbd35de5fe5_1ad4f2627f3481397f5@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 6534da24 by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: move generic cmm optimization logic in NCG to a standalone module This commit moves GHC.CmmToAsm.cmmToCmm to a standalone module, GHC.Cmm.GenericOpt. The main motivation is enabling this logic to be run in the wasm backend NCG code, which is defined in other modules that's imported by GHC.CmmToAsm, causing a cyclic dependency issue. - - - - - 87e34888 by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: explicitly disable PIC in wasm32 NCG This commit explicitly disables the ncgPIC flag for the wasm32 target. The wasm backend doesn't support PIC for the time being. - - - - - c6ce242e by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: enable generic cmm optimizations in wasm backend NCG This commit enables the generic cmm optimizations in other NCGs to be run in the wasm backend as well, followed by a late cmm control-flow optimization pass. The added optimizations do catch some corner cases not handled by the pre-NCG cmm pipeline and are useful in generating smaller CFGs. - - - - - 5 changed files: - + compiler/GHC/Cmm/GenericOpt.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Wasm.hs - compiler/GHC/Driver/Config/CmmToAsm.hs - compiler/ghc.cabal.in Changes: ===================================== compiler/GHC/Cmm/GenericOpt.hs ===================================== @@ -0,0 +1,222 @@ +-- ----------------------------------------------------------------------------- +-- +-- (c) The University of Glasgow 1993-2004 +-- +-- +-- ----------------------------------------------------------------------------- + +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE UnboxedTuples #-} + +module GHC.Cmm.GenericOpt + ( cmmToCmm + ) +where + +import GHC.Prelude hiding (head) +import GHC.Platform +import GHC.CmmToAsm.PIC +import GHC.CmmToAsm.Config +import GHC.CmmToAsm.Types +import GHC.Cmm.BlockId +import GHC.Cmm +import GHC.Cmm.Utils +import GHC.Cmm.Dataflow.Block +import GHC.Cmm.Opt ( cmmMachOpFold ) +import GHC.Cmm.CLabel +import GHC.Data.FastString +import GHC.Unit +import Control.Monad + +-- ----------------------------------------------------------------------------- +-- Generic Cmm optimiser + +{- +Here we do: + + (a) Constant folding + (c) Position independent code and dynamic linking + (i) introduce the appropriate indirections + and position independent refs + (ii) compile a list of imported symbols + (d) Some arch-specific optimizations + +(a) will be moving to the new Hoopl pipeline, however, (c) and +(d) are only needed by the native backend and will continue to live +here. + +Ideas for other things we could do (put these in Hoopl please!): + + - shortcut jumps-to-jumps + - simple CSE: if an expr is assigned to a temp, then replace later occs of + that expr with the temp, until the expr is no longer valid (can push through + temp assignments, and certain assigns to mem...) +-} + +cmmToCmm :: NCGConfig -> RawCmmDecl -> (RawCmmDecl, [CLabel]) +cmmToCmm _ top@(CmmData _ _) = (top, []) +cmmToCmm config (CmmProc info lbl live graph) + = runCmmOpt config $ + do blocks' <- mapM cmmBlockConFold (toBlockList graph) + return $ CmmProc info lbl live (ofBlockList (g_entry graph) blocks') + +type OptMResult a = (# a, [CLabel] #) + +pattern OptMResult :: a -> b -> (# a, b #) +pattern OptMResult x y = (# x, y #) +{-# COMPLETE OptMResult #-} + +newtype CmmOptM a = CmmOptM (NCGConfig -> [CLabel] -> OptMResult a) + deriving (Functor) + +instance Applicative CmmOptM where + pure x = CmmOptM $ \_ imports -> OptMResult x imports + (<*>) = ap + +instance Monad CmmOptM where + (CmmOptM f) >>= g = + CmmOptM $ \config imports0 -> + case f config imports0 of + OptMResult x imports1 -> + case g x of + CmmOptM g' -> g' config imports1 + +instance CmmMakeDynamicReferenceM CmmOptM where + addImport = addImportCmmOpt + +addImportCmmOpt :: CLabel -> CmmOptM () +addImportCmmOpt lbl = CmmOptM $ \_ imports -> OptMResult () (lbl:imports) + +getCmmOptConfig :: CmmOptM NCGConfig +getCmmOptConfig = CmmOptM $ \config imports -> OptMResult config imports + +runCmmOpt :: NCGConfig -> CmmOptM a -> (a, [CLabel]) +runCmmOpt config (CmmOptM f) = + case f config [] of + OptMResult result imports -> (result, imports) + +cmmBlockConFold :: CmmBlock -> CmmOptM CmmBlock +cmmBlockConFold block = do + let (entry, middle, last) = blockSplit block + stmts = blockToList middle + stmts' <- mapM cmmStmtConFold stmts + last' <- cmmStmtConFold last + return $ blockJoin entry (blockFromList stmts') last' + +-- This does three optimizations, but they're very quick to check, so we don't +-- bother turning them off even when the Hoopl code is active. Since +-- this is on the old Cmm representation, we can't reuse the code either: +-- * reg = reg --> nop +-- * if 0 then jump --> nop +-- * if 1 then jump --> jump +-- We might be tempted to skip this step entirely of not Opt_PIC, but +-- there is some PowerPC code for the non-PIC case, which would also +-- have to be separated. +cmmStmtConFold :: CmmNode e x -> CmmOptM (CmmNode e x) +cmmStmtConFold stmt + = case stmt of + CmmAssign reg src + -> do src' <- cmmExprConFold DataReference src + return $ case src' of + CmmReg reg' | reg == reg' -> CmmComment (fsLit "nop") + new_src -> CmmAssign reg new_src + + CmmStore addr src align + -> do addr' <- cmmExprConFold DataReference addr + src' <- cmmExprConFold DataReference src + return $ CmmStore addr' src' align + + CmmCall { cml_target = addr } + -> do addr' <- cmmExprConFold JumpReference addr + return $ stmt { cml_target = addr' } + + CmmUnsafeForeignCall target regs args + -> do target' <- case target of + ForeignTarget e conv -> do + e' <- cmmExprConFold CallReference e + return $ ForeignTarget e' conv + PrimTarget _ -> + return target + args' <- mapM (cmmExprConFold DataReference) args + return $ CmmUnsafeForeignCall target' regs args' + + CmmCondBranch test true false likely + -> do test' <- cmmExprConFold DataReference test + return $ case test' of + CmmLit (CmmInt 0 _) -> CmmBranch false + CmmLit (CmmInt _ _) -> CmmBranch true + _other -> CmmCondBranch test' true false likely + + CmmSwitch expr ids + -> do expr' <- cmmExprConFold DataReference expr + return $ CmmSwitch expr' ids + + other + -> return other + +cmmExprConFold :: ReferenceKind -> CmmExpr -> CmmOptM CmmExpr +cmmExprConFold referenceKind expr = do + config <- getCmmOptConfig + + let expr' = if not (ncgDoConstantFolding config) + then expr + else cmmExprCon config expr + + cmmExprNative referenceKind expr' + +cmmExprCon :: NCGConfig -> CmmExpr -> CmmExpr +cmmExprCon config (CmmLoad addr rep align) = CmmLoad (cmmExprCon config addr) rep align +cmmExprCon config (CmmMachOp mop args) + = cmmMachOpFold (ncgPlatform config) mop (map (cmmExprCon config) args) +cmmExprCon _ other = other + +-- handles both PIC and non-PIC cases... a very strange mixture +-- of things to do. +cmmExprNative :: ReferenceKind -> CmmExpr -> CmmOptM CmmExpr +cmmExprNative referenceKind expr = do + config <- getCmmOptConfig + let platform = ncgPlatform config + arch = platformArch platform + case expr of + CmmLoad addr rep align + -> do addr' <- cmmExprNative DataReference addr + return $ CmmLoad addr' rep align + + CmmMachOp mop args + -> do args' <- mapM (cmmExprNative DataReference) args + return $ CmmMachOp mop args' + + CmmLit (CmmBlock id) + -> cmmExprNative referenceKind (CmmLit (CmmLabel (infoTblLbl id))) + -- we must convert block Ids to CLabels here, because we + -- might have to do the PIC transformation. Hence we must + -- not modify BlockIds beyond this point. + + CmmLit (CmmLabel lbl) + -> cmmMakeDynamicReference config referenceKind lbl + CmmLit (CmmLabelOff lbl off) + -> do dynRef <- cmmMakeDynamicReference config referenceKind lbl + -- need to optimize here, since it's late + return $ cmmMachOpFold platform (MO_Add (wordWidth platform)) [ + dynRef, + (CmmLit $ CmmInt (fromIntegral off) (wordWidth platform)) + ] + + -- On powerpc (non-PIC), it's easier to jump directly to a label than + -- to use the register table, so we replace these registers + -- with the corresponding labels: + CmmReg (CmmGlobal (GlobalRegUse EagerBlackholeInfo _)) + | arch == ArchPPC && not (ncgPIC config) + -> cmmExprNative referenceKind $ + CmmLit (CmmLabel (mkCmmCodeLabel rtsUnitId (fsLit "__stg_EAGER_BLACKHOLE_info"))) + CmmReg (CmmGlobal (GlobalRegUse GCEnter1 _)) + | arch == ArchPPC && not (ncgPIC config) + -> cmmExprNative referenceKind $ + CmmLit (CmmLabel (mkCmmCodeLabel rtsUnitId (fsLit "__stg_gc_enter_1"))) + CmmReg (CmmGlobal (GlobalRegUse GCFun _)) + | arch == ArchPPC && not (ncgPIC config) + -> cmmExprNative referenceKind $ + CmmLit (CmmLabel (mkCmmCodeLabel rtsUnitId (fsLit "__stg_gc_fun"))) + + other + -> return other ===================================== compiler/GHC/CmmToAsm.hs ===================================== @@ -5,10 +5,6 @@ -- -- ----------------------------------------------------------------------------- -{-# LANGUAGE GADTs #-} -{-# LANGUAGE PatternSynonyms #-} -{-# LANGUAGE UnboxedTuples #-} - -- | Note [Native code generator] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- @@ -99,11 +95,9 @@ import GHC.Cmm.DebugBlock import GHC.Cmm.BlockId import GHC.StgToCmm.CgUtils ( fixStgRegisters ) import GHC.Cmm -import GHC.Cmm.Utils import GHC.Cmm.Dataflow.Collections import GHC.Cmm.Dataflow.Label -import GHC.Cmm.Dataflow.Block -import GHC.Cmm.Opt ( cmmMachOpFold ) +import GHC.Cmm.GenericOpt import GHC.Cmm.CLabel import GHC.Types.Unique.FM @@ -159,7 +153,7 @@ nativeCodeGen logger ts config modLoc h us cmms ArchLoongArch64->panic "nativeCodeGen: No NCG for LoongArch64" ArchUnknown -> panic "nativeCodeGen: No NCG for unknown arch" ArchJavaScript-> panic "nativeCodeGen: No NCG for JavaScript" - ArchWasm32 -> Wasm32.ncgWasm logger platform ts us modLoc h cmms + ArchWasm32 -> Wasm32.ncgWasm config logger platform ts us modLoc h cmms -- | Data accumulated during code generation. Mostly about statistics, -- but also collects debug data for DWARF generation. @@ -937,196 +931,3 @@ genMachCode config cmmTopCodeGen fileIds dbgMap cmm_top cmm_cfg , natm_fileid final_st, final_cfg) else pprPanic "genMachCode: nonzero final delta" (int final_delta) } - --- ----------------------------------------------------------------------------- --- Generic Cmm optimiser - -{- -Here we do: - - (a) Constant folding - (c) Position independent code and dynamic linking - (i) introduce the appropriate indirections - and position independent refs - (ii) compile a list of imported symbols - (d) Some arch-specific optimizations - -(a) will be moving to the new Hoopl pipeline, however, (c) and -(d) are only needed by the native backend and will continue to live -here. - -Ideas for other things we could do (put these in Hoopl please!): - - - shortcut jumps-to-jumps - - simple CSE: if an expr is assigned to a temp, then replace later occs of - that expr with the temp, until the expr is no longer valid (can push through - temp assignments, and certain assigns to mem...) --} - -cmmToCmm :: NCGConfig -> RawCmmDecl -> (RawCmmDecl, [CLabel]) -cmmToCmm _ top@(CmmData _ _) = (top, []) -cmmToCmm config (CmmProc info lbl live graph) - = runCmmOpt config $ - do blocks' <- mapM cmmBlockConFold (toBlockList graph) - return $ CmmProc info lbl live (ofBlockList (g_entry graph) blocks') - -type OptMResult a = (# a, [CLabel] #) - -pattern OptMResult :: a -> b -> (# a, b #) -pattern OptMResult x y = (# x, y #) -{-# COMPLETE OptMResult #-} - -newtype CmmOptM a = CmmOptM (NCGConfig -> [CLabel] -> OptMResult a) - deriving (Functor) - -instance Applicative CmmOptM where - pure x = CmmOptM $ \_ imports -> OptMResult x imports - (<*>) = ap - -instance Monad CmmOptM where - (CmmOptM f) >>= g = - CmmOptM $ \config imports0 -> - case f config imports0 of - OptMResult x imports1 -> - case g x of - CmmOptM g' -> g' config imports1 - -instance CmmMakeDynamicReferenceM CmmOptM where - addImport = addImportCmmOpt - -addImportCmmOpt :: CLabel -> CmmOptM () -addImportCmmOpt lbl = CmmOptM $ \_ imports -> OptMResult () (lbl:imports) - -getCmmOptConfig :: CmmOptM NCGConfig -getCmmOptConfig = CmmOptM $ \config imports -> OptMResult config imports - -runCmmOpt :: NCGConfig -> CmmOptM a -> (a, [CLabel]) -runCmmOpt config (CmmOptM f) = - case f config [] of - OptMResult result imports -> (result, imports) - -cmmBlockConFold :: CmmBlock -> CmmOptM CmmBlock -cmmBlockConFold block = do - let (entry, middle, last) = blockSplit block - stmts = blockToList middle - stmts' <- mapM cmmStmtConFold stmts - last' <- cmmStmtConFold last - return $ blockJoin entry (blockFromList stmts') last' - --- This does three optimizations, but they're very quick to check, so we don't --- bother turning them off even when the Hoopl code is active. Since --- this is on the old Cmm representation, we can't reuse the code either: --- * reg = reg --> nop --- * if 0 then jump --> nop --- * if 1 then jump --> jump --- We might be tempted to skip this step entirely of not Opt_PIC, but --- there is some PowerPC code for the non-PIC case, which would also --- have to be separated. -cmmStmtConFold :: CmmNode e x -> CmmOptM (CmmNode e x) -cmmStmtConFold stmt - = case stmt of - CmmAssign reg src - -> do src' <- cmmExprConFold DataReference src - return $ case src' of - CmmReg reg' | reg == reg' -> CmmComment (fsLit "nop") - new_src -> CmmAssign reg new_src - - CmmStore addr src align - -> do addr' <- cmmExprConFold DataReference addr - src' <- cmmExprConFold DataReference src - return $ CmmStore addr' src' align - - CmmCall { cml_target = addr } - -> do addr' <- cmmExprConFold JumpReference addr - return $ stmt { cml_target = addr' } - - CmmUnsafeForeignCall target regs args - -> do target' <- case target of - ForeignTarget e conv -> do - e' <- cmmExprConFold CallReference e - return $ ForeignTarget e' conv - PrimTarget _ -> - return target - args' <- mapM (cmmExprConFold DataReference) args - return $ CmmUnsafeForeignCall target' regs args' - - CmmCondBranch test true false likely - -> do test' <- cmmExprConFold DataReference test - return $ case test' of - CmmLit (CmmInt 0 _) -> CmmBranch false - CmmLit (CmmInt _ _) -> CmmBranch true - _other -> CmmCondBranch test' true false likely - - CmmSwitch expr ids - -> do expr' <- cmmExprConFold DataReference expr - return $ CmmSwitch expr' ids - - other - -> return other - -cmmExprConFold :: ReferenceKind -> CmmExpr -> CmmOptM CmmExpr -cmmExprConFold referenceKind expr = do - config <- getCmmOptConfig - - let expr' = if not (ncgDoConstantFolding config) - then expr - else cmmExprCon config expr - - cmmExprNative referenceKind expr' - -cmmExprCon :: NCGConfig -> CmmExpr -> CmmExpr -cmmExprCon config (CmmLoad addr rep align) = CmmLoad (cmmExprCon config addr) rep align -cmmExprCon config (CmmMachOp mop args) - = cmmMachOpFold (ncgPlatform config) mop (map (cmmExprCon config) args) -cmmExprCon _ other = other - --- handles both PIC and non-PIC cases... a very strange mixture --- of things to do. -cmmExprNative :: ReferenceKind -> CmmExpr -> CmmOptM CmmExpr -cmmExprNative referenceKind expr = do - config <- getCmmOptConfig - let platform = ncgPlatform config - arch = platformArch platform - case expr of - CmmLoad addr rep align - -> do addr' <- cmmExprNative DataReference addr - return $ CmmLoad addr' rep align - - CmmMachOp mop args - -> do args' <- mapM (cmmExprNative DataReference) args - return $ CmmMachOp mop args' - - CmmLit (CmmBlock id) - -> cmmExprNative referenceKind (CmmLit (CmmLabel (infoTblLbl id))) - -- we must convert block Ids to CLabels here, because we - -- might have to do the PIC transformation. Hence we must - -- not modify BlockIds beyond this point. - - CmmLit (CmmLabel lbl) - -> cmmMakeDynamicReference config referenceKind lbl - CmmLit (CmmLabelOff lbl off) - -> do dynRef <- cmmMakeDynamicReference config referenceKind lbl - -- need to optimize here, since it's late - return $ cmmMachOpFold platform (MO_Add (wordWidth platform)) [ - dynRef, - (CmmLit $ CmmInt (fromIntegral off) (wordWidth platform)) - ] - - -- On powerpc (non-PIC), it's easier to jump directly to a label than - -- to use the register table, so we replace these registers - -- with the corresponding labels: - CmmReg (CmmGlobal (GlobalRegUse EagerBlackholeInfo _)) - | arch == ArchPPC && not (ncgPIC config) - -> cmmExprNative referenceKind $ - CmmLit (CmmLabel (mkCmmCodeLabel rtsUnitId (fsLit "__stg_EAGER_BLACKHOLE_info"))) - CmmReg (CmmGlobal (GlobalRegUse GCEnter1 _)) - | arch == ArchPPC && not (ncgPIC config) - -> cmmExprNative referenceKind $ - CmmLit (CmmLabel (mkCmmCodeLabel rtsUnitId (fsLit "__stg_gc_enter_1"))) - CmmReg (CmmGlobal (GlobalRegUse GCFun _)) - | arch == ArchPPC && not (ncgPIC config) - -> cmmExprNative referenceKind $ - CmmLit (CmmLabel (mkCmmCodeLabel rtsUnitId (fsLit "__stg_gc_fun"))) - - other - -> return other ===================================== compiler/GHC/CmmToAsm/Wasm.hs ===================================== @@ -1,6 +1,7 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Strict #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module GHC.CmmToAsm.Wasm (ncgWasm) where @@ -9,6 +10,9 @@ import Data.ByteString.Lazy.Char8 (unpack) import Data.Maybe import Data.Semigroup import GHC.Cmm +import GHC.Cmm.ContFlowOpt +import GHC.Cmm.GenericOpt +import GHC.CmmToAsm.Config import GHC.CmmToAsm.Wasm.Asm import GHC.CmmToAsm.Wasm.FromCmm import GHC.CmmToAsm.Wasm.Types @@ -24,6 +28,7 @@ import GHC.Utils.Outputable (text) import System.IO ncgWasm :: + NCGConfig -> Logger -> Platform -> ToolSettings -> @@ -32,8 +37,8 @@ ncgWasm :: Handle -> Stream IO RawCmmGroup a -> IO a -ncgWasm logger platform ts us loc h cmms = do - (r, s) <- streamCmmGroups platform us cmms +ncgWasm ncg_config logger platform ts us loc h cmms = do + (r, s) <- streamCmmGroups ncg_config platform us cmms outputWasm $ "# " <> string7 (fromJust $ ml_hs_file loc) <> "\n\n" outputWasm $ execWasmAsmM do_tail_call $ asmTellEverything TagI32 s pure r @@ -51,17 +56,26 @@ ncgWasm logger platform ts us loc h cmms = do hPutBuilder h builder streamCmmGroups :: + NCGConfig -> Platform -> UniqSupply -> Stream IO RawCmmGroup a -> IO (a, WasmCodeGenState 'I32) -streamCmmGroups platform us cmms = - go (initialWasmCodeGenState platform us) $ - runStream cmms +streamCmmGroups ncg_config platform us cmms = + go (initialWasmCodeGenState platform us) $ runStream cmms where go s (Done r) = pure (r, s) go s (Effect m) = m >>= go s - go s (Yield cmm k) = go (wasmExecM (onCmmGroup cmm) s) k + go s (Yield decls k) = go (wasmExecM (onCmmGroup $ map opt decls) s) k + where + -- Run the generic cmm optimizations like other NCGs, followed + -- by a late control-flow optimization pass that does shrink + -- the CFG block count in some cases. + opt decl = case decl of + CmmData {} -> decl + CmmProc {} -> CmmProc info lbl live $ cmmCfgOpts False graph + where + (CmmProc info lbl live graph, _) = cmmToCmm ncg_config decl doTailCall :: ToolSettings -> Bool doTailCall ts = Option "-mtail-call" `elem` as_args ===================================== compiler/GHC/Driver/Config/CmmToAsm.hs ===================================== @@ -21,7 +21,8 @@ initNCGConfig dflags this_mod = NCGConfig , ncgAsmContext = initSDocContext dflags PprCode , ncgProcAlignment = cmmProcAlignment dflags , ncgExternalDynamicRefs = gopt Opt_ExternalDynamicRefs dflags - , ncgPIC = positionIndependent dflags + -- no PIC on wasm32 for now + , ncgPIC = positionIndependent dflags && not (platformArch (targetPlatform dflags) == ArchWasm32) , ncgInlineThresholdMemcpy = fromIntegral $ maxInlineMemcpyInsns dflags , ncgInlineThresholdMemset = fromIntegral $ maxInlineMemsetInsns dflags , ncgSplitSections = gopt Opt_SplitSections dflags ===================================== compiler/ghc.cabal.in ===================================== @@ -226,6 +226,7 @@ Library GHC.Cmm.Dataflow.Label GHC.Cmm.DebugBlock GHC.Cmm.Expr + GHC.Cmm.GenericOpt GHC.Cmm.Graph GHC.Cmm.Info GHC.Cmm.Info.Build View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/856b5e7561719ffce74595fca096082996163431...c6ce242e846a3ca05eb04abf0e7d34dbcaa62906 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/856b5e7561719ffce74595fca096082996163431...c6ce242e846a3ca05eb04abf0e7d34dbcaa62906 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 17:23:36 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 01 Feb 2024 12:23:36 -0500 Subject: [Git][ghc/ghc][master] Namespacing for WARNING/DEPRECATED pragmas (#24396) Message-ID: <65bbd39897d6f_1ad4f264a2bc01432ba@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 151dda4e by Andrei Borzenkov at 2024-02-01T12:22:43-05:00 Namespacing for WARNING/DEPRECATED pragmas (#24396) New syntax for WARNING and DEPRECATED pragmas was added, namely namespace specifierss: namespace_spec ::= 'type' | 'data' | {- empty -} warning ::= warning_category namespace_spec namelist strings deprecation ::= namespace_spec namelist strings A new data type was introduced to represent these namespace specifiers: data NamespaceSpecifier = NoSpecifier | TypeNamespaceSpecifier (EpToken "type") | DataNamespaceSpecifier (EpToken "data") Extension field XWarning now contains this NamespaceSpecifier. lookupBindGroupOcc function was changed: it now takes NamespaceSpecifier and checks that the namespace of the found names matches the passed flag. With this change {-# WARNING data D "..." #-} pragma will only affect value namespace and {-# WARNING type D "..." #-} will only affect type namespace. The same logic is applicable to DEPRECATED pragmas. Finding duplicated warnings inside rnSrcWarnDecls now takes into consideration NamespaceSpecifier flag to allow warnings with the same names that refer to different namespaces. - - - - - 13 changed files: - compiler/GHC/Hs/Decls.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Module.hs - docs/users_guide/9.10.1-notes.rst - docs/users_guide/exts/pragmas.rst - libraries/ghc-prim/GHC/Tuple.hs - + testsuite/tests/warnings/should_compile/T24396.stderr - + testsuite/tests/warnings/should_compile/T24396a.hs - + testsuite/tests/warnings/should_compile/T24396b.hs - testsuite/tests/warnings/should_compile/all.T - utils/check-exact/ExactPrint.hs Changes: ===================================== compiler/GHC/Hs/Decls.hs ===================================== @@ -81,8 +81,9 @@ module GHC.Hs.Decls ( -- ** Document comments DocDecl(..), LDocDecl, docDeclDoc, -- ** Deprecations - WarnDecl(..), LWarnDecl, + WarnDecl(..), NamespaceSpecifier(..), LWarnDecl, WarnDecls(..), LWarnDecls, + overlappingNamespaceSpecifiers, coveredByNamespaceSpecifier, -- ** Annotations AnnDecl(..), LAnnDecl, AnnProvenance(..), annProvenanceName_maybe, @@ -120,7 +121,7 @@ import GHC.Types.Name.Set import GHC.Types.Fixity -- others: -import GHC.Utils.Misc (count) +import GHC.Utils.Misc (count, (<||>)) import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Types.SrcLoc @@ -1280,9 +1281,30 @@ type instance XWarnings GhcTc = SourceText type instance XXWarnDecls (GhcPass _) = DataConCantHappen -type instance XWarning (GhcPass _) = EpAnn [AddEpAnn] +type instance XWarning (GhcPass _) = (NamespaceSpecifier, EpAnn [AddEpAnn]) type instance XXWarnDecl (GhcPass _) = DataConCantHappen +data NamespaceSpecifier + = NoNamespaceSpecifier + | TypeNamespaceSpecifier (EpToken "type") + | DataNamespaceSpecifier (EpToken "data") + deriving (Data) + +overlappingNamespaceSpecifiers :: NamespaceSpecifier -> NamespaceSpecifier -> Bool +overlappingNamespaceSpecifiers NoNamespaceSpecifier _ = True +overlappingNamespaceSpecifiers _ NoNamespaceSpecifier = True +overlappingNamespaceSpecifiers TypeNamespaceSpecifier{} TypeNamespaceSpecifier{} = True +overlappingNamespaceSpecifiers DataNamespaceSpecifier{} DataNamespaceSpecifier{} = True +overlappingNamespaceSpecifiers _ _ = False + +coveredByNamespaceSpecifier :: NamespaceSpecifier -> NameSpace -> Bool +coveredByNamespaceSpecifier NoNamespaceSpecifier = const True +coveredByNamespaceSpecifier TypeNamespaceSpecifier{} = isTcClsNameSpace <||> isTvNameSpace +coveredByNamespaceSpecifier DataNamespaceSpecifier{} = isValNameSpace +instance Outputable NamespaceSpecifier where + ppr NoNamespaceSpecifier = empty + ppr TypeNamespaceSpecifier{} = text "type" + ppr DataNamespaceSpecifier{} = text "data" instance OutputableBndrId p => Outputable (WarnDecls (GhcPass p)) where @@ -1296,8 +1318,9 @@ instance OutputableBndrId p instance OutputableBndrId p => Outputable (WarnDecl (GhcPass p)) where - ppr (Warning _ thing txt) + ppr (Warning (ns_spec, _) thing txt) = ppr_category + <+> ppr ns_spec <+> hsep (punctuate comma (map ppr thing)) <+> ppr txt where ===================================== compiler/GHC/Parser.y ===================================== @@ -1985,10 +1985,15 @@ warnings :: { OrdList (LWarnDecl GhcPs) } -- SUP: TEMPORARY HACK, not checking for `module Foo' warning :: { OrdList (LWarnDecl GhcPs) } - : warning_category namelist strings - {% fmap unitOL $ acsA (\cs -> L (comb3 $1 $2 $3) - (Warning (EpAnn (glMR $1 $2) (fst $ unLoc $3) cs) (unLoc $2) - (WarningTxt $1 NoSourceText $ map stringLiteralToHsDocWst $ snd $ unLoc $3))) } + : warning_category namespace_spec namelist strings + {% fmap unitOL $ acsA (\cs -> L (comb4 $1 $2 $3 $4) + (Warning (unLoc $2, EpAnn (glMR $1 $3) (fst $ unLoc $4) cs) (unLoc $3) + (WarningTxt $1 NoSourceText $ map stringLiteralToHsDocWst $ snd $ unLoc $4))) } + +namespace_spec :: { Located NamespaceSpecifier } + : 'type' { sL1 $1 $ TypeNamespaceSpecifier (epTok $1) } + | 'data' { sL1 $1 $ DataNamespaceSpecifier (epTok $1) } + | {- empty -} { sL0 $ NoNamespaceSpecifier } deprecations :: { OrdList (LWarnDecl GhcPs) } : deprecations ';' deprecation @@ -2009,9 +2014,9 @@ deprecations :: { OrdList (LWarnDecl GhcPs) } -- SUP: TEMPORARY HACK, not checking for `module Foo' deprecation :: { OrdList (LWarnDecl GhcPs) } - : namelist strings - {% fmap unitOL $ acsA (\cs -> sLL $1 $> $ (Warning (EpAnn (glEE $1 $>) (fst $ unLoc $2) cs) (unLoc $1) - (DeprecatedTxt NoSourceText $ map stringLiteralToHsDocWst $ snd $ unLoc $2))) } + : namespace_spec namelist strings + {% fmap unitOL $ acsA (\cs -> sL (comb3 $1 $2 $>) $ (Warning (unLoc $1, EpAnn (glEE $2 $>) (fst $ unLoc $3) cs) (unLoc $2) + (DeprecatedTxt NoSourceText $ map stringLiteralToHsDocWst $ snd $ unLoc $3))) } strings :: { Located ([AddEpAnn],[Located StringLiteral]) } : STRING { sL1 $1 ([],[L (gl $1) (getStringLiteral $1)]) } ===================================== compiler/GHC/Rename/Bind.hs ===================================== @@ -1388,7 +1388,7 @@ rnSrcFixityDecl sig_ctxt = rn_decl = setSrcSpanA name_loc $ -- This lookup will fail if the name is not defined in the -- same binding group as this fixity declaration. - do names <- lookupLocalTcNames sig_ctxt what rdr_name + do names <- lookupLocalTcNames sig_ctxt what NoNamespaceSpecifier rdr_name return [ L name_loc name | (_, name) <- names ] what = text "fixity signature" ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -2068,7 +2068,7 @@ lookupSigCtxtOccRn :: HsSigCtxt lookupSigCtxtOccRn ctxt what = wrapLocMA $ \ rdr_name -> do { let also_try_tycons = False - ; mb_names <- lookupBindGroupOcc ctxt what rdr_name also_try_tycons + ; mb_names <- lookupBindGroupOcc ctxt what rdr_name also_try_tycons NoNamespaceSpecifier ; case mb_names of Right name NE.:| rest -> do { massertPpr (null rest) $ @@ -2085,12 +2085,13 @@ lookupBindGroupOcc :: HsSigCtxt -> Bool -- ^ if the 'RdrName' we are looking up is in -- a value 'NameSpace', should we also look up -- in the type constructor 'NameSpace'? + -> NamespaceSpecifier -> RnM (NE.NonEmpty (Either NotInScopeError Name)) -- ^ Looks up the 'RdrName', expecting it to resolve to one of the -- bound names currently in scope. If not, return an appropriate error message. -- -- See Note [Looking up signature names]. -lookupBindGroupOcc ctxt what rdr_name also_try_tycon_ns +lookupBindGroupOcc ctxt what rdr_name also_try_tycon_ns ns_spec | Just n <- isExact_maybe rdr_name = do { mb_gre <- lookupExactOcc_either n ; return $ case mb_gre of @@ -2105,24 +2106,27 @@ lookupBindGroupOcc ctxt what rdr_name also_try_tycon_ns | otherwise = case ctxt of - HsBootCtxt ns -> lookup_top (`elemNameSet` ns) - TopSigCtxt ns -> lookup_top (`elemNameSet` ns) - RoleAnnotCtxt ns -> lookup_top (`elemNameSet` ns) + HsBootCtxt ns -> lookup_top (elem_name_set_with_namespace ns) + TopSigCtxt ns -> lookup_top (elem_name_set_with_namespace ns) + RoleAnnotCtxt ns -> lookup_top (elem_name_set_with_namespace ns) LocalBindCtxt ns -> lookup_group ns ClsDeclCtxt cls -> lookup_cls_op cls InstDeclCtxt ns -> if uniqSetAny isUnboundName ns -- #16610 then return $ NE.singleton $ Right $ mkUnboundNameRdr rdr_name - else lookup_top (`elemNameSet` ns) + else lookup_top (elem_name_set_with_namespace ns) where + elem_name_set_with_namespace ns n = check_namespace n && (n `elemNameSet` ns) - ns = occNameSpace occ + check_namespace = coveredByNamespaceSpecifier ns_spec . nameNameSpace + + namespace = occNameSpace occ occ = rdrNameOcc rdr_name relevant_gres = RelevantGREs { includeFieldSelectors = WantBoth , lookupVariablesForFields = True , lookupTyConsAsWell = also_try_tycon_ns } - ok_gre = greIsRelevant relevant_gres ns + ok_gre = greIsRelevant relevant_gres namespace finish err gre | ok_gre gre @@ -2180,16 +2184,16 @@ lookupBindGroupOcc ctxt what rdr_name also_try_tycon_ns --------------- -lookupLocalTcNames :: HsSigCtxt -> SDoc -> RdrName -> RnM [(RdrName, Name)] +lookupLocalTcNames :: HsSigCtxt -> SDoc -> NamespaceSpecifier -> RdrName -> RnM [(RdrName, Name)] -- GHC extension: look up both the tycon and data con or variable. -- Used for top-level fixity signatures and deprecations. -- Complain if neither is in scope. -- See Note [Fixity signature lookup] -lookupLocalTcNames ctxt what rdr +lookupLocalTcNames ctxt what ns_spec rdr = do { this_mod <- getModule ; let also_try_tycon_ns = True ; nms_eithers <- fmap (guard_builtin_syntax this_mod rdr) <$> - lookupBindGroupOcc ctxt what rdr also_try_tycon_ns + lookupBindGroupOcc ctxt what rdr also_try_tycon_ns ns_spec ; let (errs, names) = partitionEithers (NE.toList nms_eithers) ; when (null names) $ addErr (head errs) -- Bleat about one only ===================================== compiler/GHC/Rename/Module.hs ===================================== @@ -273,7 +273,7 @@ rnSrcWarnDecls _ [] rnSrcWarnDecls bndr_set decls' = do { -- check for duplicates - ; mapM_ (\ dups -> let ((L loc rdr) :| (lrdr':_)) = dups + ; mapM_ (\ dups -> let ((L loc rdr) :| (lrdr':_)) = fmap snd dups in addErrAt (locA loc) (TcRnDuplicateWarningDecls lrdr' rdr)) warn_rdr_dups ; pairs_s <- mapM (addLocM rn_deprec) decls @@ -283,9 +283,9 @@ rnSrcWarnDecls bndr_set decls' sig_ctxt = TopSigCtxt bndr_set - rn_deprec (Warning _ rdr_names txt) + rn_deprec (Warning (ns_spec, _) rdr_names txt) -- ensures that the names are defined locally - = do { names <- concatMapM (lookupLocalTcNames sig_ctxt what . unLoc) + = do { names <- concatMapM (lookupLocalTcNames sig_ctxt what ns_spec . unLoc) rdr_names ; txt' <- rnWarningTxt txt ; return [(nameOccName nm, txt') | (_, nm) <- names] } @@ -295,8 +295,13 @@ rnSrcWarnDecls bndr_set decls' what = text "deprecation" - warn_rdr_dups = findDupRdrNames - $ concatMap (\(L _ (Warning _ ns _)) -> ns) decls + warn_rdr_dups = find_dup_warning_names + $ concatMap (\(L _ (Warning (ns_spec, _) ns _)) -> (ns_spec,) <$> ns) decls + + find_dup_warning_names :: [(NamespaceSpecifier, LocatedN RdrName)] -> [NonEmpty (NamespaceSpecifier, LocatedN RdrName)] + find_dup_warning_names = findDupsEq (\ (spec1, x) -> \ (spec2, y) -> + overlappingNamespaceSpecifiers spec1 spec2 && + rdrNameOcc (unLoc x) == rdrNameOcc (unLoc y)) rnWarningTxt :: WarningTxt GhcPs -> RnM (WarningTxt GhcRn) rnWarningTxt (WarningTxt mb_cat st wst) = do @@ -312,9 +317,6 @@ rnWarningTxt (DeprecatedTxt st wst) = do rnLWarningTxt :: LWarningTxt GhcPs -> RnM (LWarningTxt GhcRn) rnLWarningTxt (L loc warn) = L loc <$> rnWarningTxt warn -findDupRdrNames :: [LocatedN RdrName] -> [NonEmpty (LocatedN RdrName)] -findDupRdrNames = findDupsEq (\ x -> \ y -> rdrNameOcc (unLoc x) == rdrNameOcc (unLoc y)) - -- look for duplicates among the OccNames; -- we check that the names are defined above -- invt: the lists returned by findDupsEq always have at least two elements ===================================== docs/users_guide/9.10.1-notes.rst ===================================== @@ -73,6 +73,18 @@ Language Library authors are advised to use a different name for their functions, such as ``forAll``, ``for_all``, or ``forall_``. +- GHC Proposal `#65 `_ + "Require namespacing fixity declarations for type names and WARNING/DEPRECATED pragmas" has been partially implemented. + Now you can specify namespace of a name that you want to warn about or deprecate: :: + + {-# DEPRACATED type D "Use `()` instead" #-} -- this will deprecate type D, but will not touch pattern synonym + data D = MkD + + {-# DEPRECATED data D "Use `MkD` instead" #-} -- this will deprecate pattern synonym only + pattern D = MkD + + Ditto for ``{-# WARNING ... #-}`` pragmas. + Compiler ~~~~~~~~ ===================================== docs/users_guide/exts/pragmas.rst ===================================== @@ -241,6 +241,24 @@ Alternatively, warnings from all ``WARNING`` and ``DEPRECATED`` pragmas regardless of category can be suppressed with :ghc-flag:`-Wno-extended-warnings <-Wextended-warnings>`. +When a deprecated name appears in both value and type namespaces (i.e. punning occurs) +``WARNING`` and ``DEPRECATED`` pragmas will affect both: :: + + {-# LANGUAGE PatternSynonyms #-} + + data D = MkD + pattern D = MkD + {-# DEPRECATED D "This will deprecate both the type D and the pattern synonym D" #-} + +It is possible to specify the namespace of the name to be warned about +or deprecated using ``type`` and ``data`` specifiers: :: + + {-# LANGUAGE PatternSynonyms #-} + + data D = MkD + pattern D = MkD + {-# DEPRECATED data D "This will deprecate only the pattern synonym D" #-} + {-# DEPRECATED type D "This will deprecate only the type D" #-} .. _minimal-pragma: @@ -1119,5 +1137,3 @@ are written immediately after the ``instance`` keyword, like this: :: instance {-# OVERLAPPING #-} C t where ... - - ===================================== libraries/ghc-prim/GHC/Tuple.hs ===================================== @@ -28,7 +28,7 @@ import GHC.Tuple.Prim default () -- Double and Integer aren't available yet -{-# DEPRECATED Solo "The Solo constructor has been renamed to MkSolo to avoid punning." #-} +{-# DEPRECATED data Solo "The Solo constructor has been renamed to MkSolo to avoid punning." #-} pattern Solo :: a -> Solo a pattern Solo x = MkSolo x {-# COMPLETE Solo #-} ===================================== testsuite/tests/warnings/should_compile/T24396.stderr ===================================== @@ -0,0 +1,68 @@ +[1 of 2] Compiling T24396a ( T24396a.hs, T24396a.o ) +[2 of 2] Compiling T24396b ( T24396b.hs, T24396b.o ) + +T24396b.hs:8:7: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)] + In the use of type constructor or class ‘C1’ + (imported from T24396a): + Deprecated: "Type deprecation" + +T24396b.hs:9:6: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)] + In the use of data constructor ‘C1’ (imported from T24396a): + Deprecated: "Data deprecation" + +T24396b.hs:11:7: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)] + In the use of type constructor or class ‘D2’ + (imported from T24396a): + Deprecated: "Type deprecation" + +T24396b.hs:12:6: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)] + In the use of data constructor ‘D2’ (imported from T24396a): + Deprecated: "Data deprecation" + +T24396b.hs:14:7: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)] + In the use of type constructor or class ‘D3’ + (imported from T24396a): + Deprecated: "Both namespace deprecation" + +T24396b.hs:15:6: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)] + In the use of data constructor ‘D3’ (imported from T24396a): + Deprecated: "Both namespace deprecation" + +T24396b.hs:17:7: warning: [GHC-63394] [-Wdeprecations (in -Wextended-warnings)] + In the use of type constructor or class ‘C2’ + (imported from T24396a): + "Type warning" + +T24396b.hs:18:6: warning: [GHC-63394] [-Wdeprecations (in -Wextended-warnings)] + In the use of data constructor ‘C2’ (imported from T24396a): + "Data warning" + +T24396b.hs:20:7: warning: [GHC-63394] [-Wdeprecations (in -Wextended-warnings)] + In the use of type constructor or class ‘D5’ + (imported from T24396a): + "Type warning" + +T24396b.hs:21:6: warning: [GHC-63394] [-Wdeprecations (in -Wextended-warnings)] + In the use of data constructor ‘D5’ (imported from T24396a): + "Data warning" + +T24396b.hs:23:7: warning: [GHC-63394] [-Wdeprecations (in -Wextended-warnings)] + In the use of type constructor or class ‘D6’ + (imported from T24396a): + "Both namespace warning" + +T24396b.hs:24:6: warning: [GHC-63394] [-Wdeprecations (in -Wextended-warnings)] + In the use of data constructor ‘D6’ (imported from T24396a): + "Both namespace warning" + +T24396b.hs:26:14: warning: [GHC-63394] [-Wdeprecations (in -Wextended-warnings)] + In the use of type constructor or class ‘$’ + (imported from T24396a): + "Type operator warning" + +T24396b.hs:27:8: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)] + In the use of data constructor ‘Solo’ (imported from GHC.Tuple): + Deprecated: "The Solo constructor has been renamed to MkSolo to avoid punning." + +T24396b.hs:27:13: warning: [GHC-63394] [-Wdeprecations (in -Wextended-warnings)] + In the use of ‘$’ (imported from T24396a): "Value operator warning" ===================================== testsuite/tests/warnings/should_compile/T24396a.hs ===================================== @@ -0,0 +1,31 @@ +module T24396a where + +class C1 +data D1 = C1 + +data D2 = D2 + +{-# DEPRECATED data C1, D2 "Data deprecation" #-} +{-# DEPRECATED type C1, D2 "Type deprecation" #-} + +data D3 = D3 +{-# DEPRECATED D3 "Both namespace deprecation" #-} + +class C2 +data D4 = C2 + +data D5 = D5 + +{-# WARNING data C2, D5 "Data warning" #-} +{-# WARNING type C2, D5 "Type warning" #-} + +data D6 = D6 +{-# WARNING D6 "Both namespace warning" #-} + +($) :: (a -> b) -> a -> b +f $ x = f x + +type f $ x = f x + +{-# WARNING data ($) "Value operator warning" #-} +{-# WARNING type ($) "Type operator warning" #-} ===================================== testsuite/tests/warnings/should_compile/T24396b.hs ===================================== @@ -0,0 +1,27 @@ +module T24396b where + +import GHC.Tuple +import Prelude hiding (($)) + +import T24396a + +d1 :: C1 => D1 +d1 = C1 + +d2 :: D2 +d2 = D2 + +d3 :: D3 +d3 = D3 + +d4 :: C2 => D4 +d4 = C2 + +d5 :: D5 +d5 = D5 + +d6 :: D6 +d6 = D6 + +solo :: Solo $ () +solo = Solo $ () ===================================== testsuite/tests/warnings/should_compile/all.T ===================================== @@ -69,3 +69,4 @@ test('T22826', normal, compile, ['']) test('T23573', [extra_files(["T23573.hs", "T23573A.hs", "T23573B.hs"])], multimod_compile, ['T23573', '-v0']) test('T23465', normal, compile, ['-ddump-parsed']) test('WarnNoncanonical', normal, compile, ['']) +test('T24396', [extra_files(["T24396a.hs", "T24396b.hs"])], multimod_compile, ['T24396b', '']) ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -1964,23 +1964,35 @@ instance ExactPrint (WarnDecls GhcPs) where -- --------------------------------------------------------------------- instance ExactPrint (WarnDecl GhcPs) where - getAnnotationEntry (Warning an _ _) = fromAnn an - setAnnotationAnchor (Warning an a b) anc ts cs = Warning (setAnchorEpa an anc ts cs) a b + getAnnotationEntry (Warning (_, an) _ _) = fromAnn an + setAnnotationAnchor (Warning (ns_spec, an) a b) anc ts cs + = Warning (ns_spec, setAnchorEpa an anc ts cs) a b - exact (Warning an lns (WarningTxt mb_cat src ls )) = do + exact (Warning (ns_spec, an) lns (WarningTxt mb_cat src ls )) = do mb_cat' <- markAnnotated mb_cat + ns_spec' <- exactNsSpec ns_spec lns' <- markAnnotated lns an0 <- markEpAnnL an lidl AnnOpenS -- "[" ls' <- markAnnotated ls an1 <- markEpAnnL an0 lidl AnnCloseS -- "]" - return (Warning an1 lns' (WarningTxt mb_cat' src ls')) + return (Warning (ns_spec', an1) lns' (WarningTxt mb_cat' src ls')) - exact (Warning an lns (DeprecatedTxt src ls)) = do + exact (Warning (ns_spec, an) lns (DeprecatedTxt src ls)) = do + ns_spec' <- exactNsSpec ns_spec lns' <- markAnnotated lns an0 <- markEpAnnL an lidl AnnOpenS -- "[" ls' <- markAnnotated ls an1 <- markEpAnnL an0 lidl AnnCloseS -- "]" - return (Warning an1 lns' (DeprecatedTxt src ls')) + return (Warning (ns_spec', an1) lns' (DeprecatedTxt src ls')) + +exactNsSpec :: (Monad m, Monoid w) => NamespaceSpecifier -> EP w m NamespaceSpecifier +exactNsSpec NoNamespaceSpecifier = pure NoNamespaceSpecifier +exactNsSpec (TypeNamespaceSpecifier type_) = do + type_' <- markEpToken type_ + pure (TypeNamespaceSpecifier type_') +exactNsSpec (DataNamespaceSpecifier data_) = do + data_' <- markEpToken data_ + pure (DataNamespaceSpecifier data_') -- --------------------------------------------------------------------- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/151dda4efcbfafd58c8d44e9f991ec241a49d515 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/151dda4efcbfafd58c8d44e9f991ec241a49d515 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 17:24:24 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 01 Feb 2024 12:24:24 -0500 Subject: [Git][ghc/ghc][master] CI: Disable the test-cabal-reinstall job Message-ID: <65bbd3c84da1b_1ad4f2667ad1c146235@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 38c3afb6 by Bryan Richter at 2024-02-01T12:23:19-05:00 CI: Disable the test-cabal-reinstall job Fixes #24363 - - - - - 1 changed file: - .gitlab-ci.yml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -483,16 +483,21 @@ stack-hadrian-build: # Testing reinstallable ghc codepath #################################### -test-cabal-reinstall-x86_64-linux-deb10: - extends: nightly-x86_64-linux-deb10-validate - stage: full-build - variables: - REINSTALL_GHC: "yes" - BUILD_FLAVOUR: validate - TEST_ENV: "x86_64-linux-deb10-cabal-install" - rules: - - if: $NIGHTLY - - if: '$CI_MERGE_REQUEST_LABELS =~ /.*test-reinstall.*/' +# As documented on the original ticket #19896, this feature already has a long +# way to go before it can actually be used. Meanwhile, parts of it have +# bit-rotted, possibly related to some Cabal change. The job is disabled for +# now. +# +# test-cabal-reinstall-x86_64-linux-deb10: +# extends: nightly-x86_64-linux-deb10-validate +# stage: full-build +# variables: +# REINSTALL_GHC: "yes" +# BUILD_FLAVOUR: validate +# TEST_ENV: "x86_64-linux-deb10-cabal-install" +# rules: +# - if: $NIGHTLY +# - if: '$CI_MERGE_REQUEST_LABELS =~ /.*test-reinstall.*/' ######################################## # Testing ABI is invariant across builds View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/38c3afb64d3ffc42f12163c6f0f0d5c414aa8255 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/38c3afb64d3ffc42f12163c6f0f0d5c414aa8255 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 17:24:50 2024 From: gitlab at gitlab.haskell.org (Matthew Craven (@clyring)) Date: Thu, 01 Feb 2024 12:24:50 -0500 Subject: [Git][ghc/ghc][wip/bump-bytestring-0.12.1-dev] 195 commits: Suppress duplicate librares linker warning of new macOS linker Message-ID: <65bbd3e28067b_1ad4f266d63241478a3@gitlab.mail> Matthew Craven pushed to branch wip/bump-bytestring-0.12.1-dev at Glasgow Haskell Compiler / GHC Commits: e98051a5 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 Suppress duplicate librares linker warning of new macOS linker Fixes #24167 XCode 15 introduced a new linker which warns on duplicate libraries being linked. To disable this warning, we pass -Wl,-no_warn_duplicate_libraries as suggested by Brad King in CMake issue #25297. This flag isn't necessarily available to other linkers on darwin, so we must only configure it into the CC linker arguments if valid. - - - - - c411c431 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Encoding test witnesses recent iconv bug is fragile A regression in the new iconv() distributed with XCode 15 and MacOS Sonoma causes the test 'encoding004' to fail in the CP936 roundrip. We mark this test as fragile until this is fixed upstream (rather than broken, since previous versions of iconv pass the test) See #24161 - - - - - ce7fe5a9 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Update to LC_ALL=C no longer being ignored in darwin MacOS seems to have fixed an issue where it used to ignore the variable `LC_ALL` in program invocations and default to using Unicode. Since the behaviour seems to be fixed to account for the locale variable, we mark tests that were previously broken in spite of it as fragile (since they now pass in recent macOS distributions) See #24161 - - - - - e6c803f7 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 darwin: Fix single_module is obsolete warning In XCode 15's linker, -single_module is the default and otherwise passing it as a flag results in a warning being raised: ld: warning: -single_module is obsolete This patch fixes this warning by, at configure time, determining whether the linker supports -single_module (which is likely false for all non-darwin linkers, and true for darwin linkers in previous versions of macOS), and using that information at runtime to decide to pass or not the flag in the invocation. Fixes #24168 - - - - - 929ba2f9 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Skip MultiLayerModulesTH_Make on darwin The recent toolchain upgrade on darwin machines resulted in the MultiLayerModulesTH_Make test metrics varying too much from the baseline, ultimately blocking the CI pipelines. This commit skips the test on darwin to temporarily avoid failures due to the environment change in the runners. However, the metrics divergence is being investigated still (tracked in #24177) - - - - - af261ccd by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 configure: check target (not build) understands -no_compact_unwind Previously, we were branching on whether the build system was darwin to shortcut this check, but we really want to branch on whether the target system (which is what we are configuring ld_prog for) is darwin. - - - - - 2125c176 by Luite Stegeman at 2023-11-15T13:19:38-05:00 JS: Fix missing variable declarations The JStg IR update was missing some local variable declarations that were present earlier, causing global variables to be used implicitly (or an error in JavaScript strict mode). This adds the local variable declarations again. - - - - - 99ced73b by Krzysztof Gogolewski at 2023-11-15T13:20:14-05:00 Remove loopy superclass solve mechanism Programs with a -Wloopy-superclass-solve warning will now fail with an error. Fixes #23017 - - - - - 2aff2361 by Zubin Duggal at 2023-11-15T13:20:50-05:00 users-guide: Fix links to libraries from the users-guide. The unit-ids generated in c1a3ecde720b3bddc2c8616daaa06ee324e602ab include the package name, so we don't need to explicitly add it to the links. Fixes #24151 - - - - - 27981fac by Alan Zimmerman at 2023-11-15T13:21:25-05:00 EPA: splitLHsForAllTyInvis does not return ann We did not use the annotations returned from splitLHsForAllTyInvis, so do not return them. - - - - - a6467834 by Krzysztof Gogolewski at 2023-11-15T22:22:59-05:00 Document defaulting of RuntimeReps Fixes #24099 - - - - - 2776920e by Simon Peyton Jones at 2023-11-15T22:23:35-05:00 Second fix to #24083 My earlier fix turns out to be too aggressive for data/type families See wrinkle (DTV1) in Note [Disconnected type variables] - - - - - cee81370 by Sylvain Henry at 2023-11-16T09:57:46-05:00 Fix unusable units and module reexport interaction (#21097) This commit fixes an issue with ModUnusable introduced in df0f148feae. In mkUnusableModuleNameProvidersMap we traverse the list of unusable units and generate ModUnusable origin for all the modules they contain: exposed modules, hidden modules, and also re-exported modules. To do this we have a two-level map: ModuleName -> Unit:ModuleName (aka Module) -> ModuleOrigin So for each module name "M" in broken unit "u" we have: "M" -> u:M -> ModUnusable reason However in the case of module reexports we were using the *target* module as a key. E.g. if "u:M" is a reexport for "X" from unit "o": "M" -> o:X -> ModUnusable reason Case 1: suppose a reexport without module renaming (u:M -> o:M) from unusable unit u: "M" -> o:M -> ModUnusable reason Here it's claiming that the import of M is unusable because a reexport from u is unusable. But if unit o isn't unusable we could also have in the map: "M" -> o:M -> ModOrigin ... Issue: the Semigroup instance of ModuleOrigin doesn't handle the case (ModUnusable <> ModOrigin) Case 2: similarly we could have 2 unusable units reexporting the same module without renaming, say (u:M -> o:M) and (v:M -> o:M) with u and v unusable. It gives: "M" -> o:M -> ModUnusable ... (for u) "M" -> o:M -> ModUnusable ... (for v) Issue: the Semigroup instance of ModuleOrigin doesn't handle the case (ModUnusable <> ModUnusable). This led to #21097, #16996, #11050. To fix this, in this commit we make ModUnusable track whether the module used as key is a reexport or not (for better error messages) and we use the re-export module as key. E.g. if "u:M" is a reexport for "o:X" and u is unusable, we now record: "M" -> u:M -> ModUnusable reason reexported=True So now, we have two cases for a reexport u:M -> o:X: - u unusable: "M" -> u:M -> ModUnusable ... reexported=True - u usable: "M" -> o:X -> ModOrigin ... reexportedFrom=u:M The second case is indexed with o:X because in this case the Semigroup instance of ModOrigin is used to combine valid expositions of a module (directly or via reexports). Note that module lookup functions select usable modules first (those who have a ModOrigin value), so it doesn't matter if we add new ModUnusable entries in the map like this: "M" -> { u:M -> ModUnusable ... reexported=True o:M -> ModOrigin ... } The ModOrigin one will be used. Only if there is no ModOrigin or ModHidden entry will the ModUnusable error be printed. See T21097 for an example printing several reasons why an import is unusable. - - - - - 3e606230 by Krzysztof Gogolewski at 2023-11-16T09:58:22-05:00 Fix IPE test A helper function was defined in a different module than used. To reproduce: ./hadrian/build test --test-root-dirs=testsuite/tests/rts/ipe - - - - - 49f5264b by Andreas Klebinger at 2023-11-16T20:52:11-05:00 Properly compute unpacked sizes for -funpack-small-strict-fields. Use rep size rather than rep count to compute the size. Fixes #22309 - - - - - b4f84e4b by James Henri Haydon at 2023-11-16T20:52:53-05:00 Explicit methods for Alternative Compose Explicitly define some and many in Alternative instance for Data.Functor.Compose Implementation of https://github.com/haskell/core-libraries-committee/issues/181 - - - - - 9bc0dd1f by Ignat Insarov at 2023-11-16T20:53:34-05:00 Add permutations for non-empty lists. Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837 - - - - - 5643ecf9 by Andrew Lelechenko at 2023-11-16T20:53:34-05:00 Update changelog and since annotations for Data.List.NonEmpty.permutations Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837 - - - - - 94ff2134 by Oleg Alexander at 2023-11-16T20:54:15-05:00 Update doc string for traceShow Updated doc string for traceShow. - - - - - faff671a by Luite Stegeman at 2023-11-17T14:12:51+01:00 JS: clean up some foreign imports - - - - - 856e0a4e by Sven Tennie at 2023-11-18T06:54:11-05:00 AArch64: Remove unused instructions As these aren't ever emitted, we don't even know if they work or will ever be used. If one of them is needed in future, we may easily re-add it. Deleted instructions are: - CMN - ANDS - BIC - BICS - EON - ORN - ROR - TST - STP - LDP - DMBSY - - - - - 615441ef by Alan Zimmerman at 2023-11-18T06:54:46-05:00 EPA: Replace Monoid with NoAnn Remove the final Monoid instances in the exact print infrastructure. For Windows CI Metric Decrease: T5205 - - - - - 5a6c49d4 by David Feuer at 2023-11-20T18:53:18-05:00 Speed up stimes in instance Semigroup Endo As discussed at https://github.com/haskell/core-libraries-committee/issues/4 - - - - - cf9da4b3 by Andrew Lelechenko at 2023-11-20T18:53:18-05:00 base: reflect latest changes in the changelog - - - - - 48bf364e by Alan Zimmerman at 2023-11-20T18:53:54-05:00 EPA: Use SrcSpan in EpaSpan This is more natural, since we already need to deal with invalid RealSrcSpans, and that is exactly what SrcSpan.UnhelpfulSpan is for. Updates haddock submodule. - - - - - 97ec37cc by Sebastian Graf at 2023-11-20T18:54:31-05:00 Add regression test for #6070 Fixes #6070. - - - - - e9d5ae41 by Owen Shepherd at 2023-11-21T18:32:23-05:00 chore: Correct typo in the gitlab MR template [skip ci] - - - - - f158a8d0 by Rodrigo Mesquita at 2023-11-21T18:32:59-05:00 Improve error message when reading invalid `.target` files A `.target` file generated by ghc-toolchain or by configure can become invalid if the target representation (`Toolchain.Target`) is changed while the files are not re-generated by calling `./configure` or `ghc-toolchain` again. There is also the issue of hadrian caching the dependencies on `.target` files, which makes parsing fail when reading reading the cached value if the representation has been updated. This patch provides a better error message in both situations, moving away from a terrible `Prelude.read: no parse` error that you would get otherwise. Fixes #24199 - - - - - 955520c6 by Ben Gamari at 2023-11-21T18:33:34-05:00 users guide: Note that QuantifiedConstraints implies ExplicitForAll Fixes #24025. - - - - - 17ec3e97 by Owen Shepherd at 2023-11-22T09:37:28+01:00 fix: Change type signatures in NonEmpty export comments to reflect reality This fixes several typos in the comments of Data.List.NonEmpty export list items. - - - - - 2fd78f9f by Samuel Thibault at 2023-11-22T11:49:13-05:00 Fix the platform string for GNU/Hurd As commited in Cargo https://github.com/haskell/cabal/pull/9434 there is confusion between "gnu" and "hurd". This got fixed in Cargo, we need the converse in Hadrian. Fixes #24180 - - - - - a79960fe by Alan Zimmerman at 2023-11-22T11:49:48-05:00 EPA: Tuple Present no longer has annotation The Present constructor for a Tuple argument will never have an exact print annotation. So make this impossible. - - - - - 121c9ab7 by David Binder at 2023-11-22T21:12:29-05:00 Unify the hpc testsuites The hpc testsuite was split between testsuite/tests/hpc and the submodule libraries/hpc/test. This commit unifies the two testsuites in the GHC repository in the directory testsuite/tests/hpc. - - - - - d2733a05 by Alan Zimmerman at 2023-11-22T21:13:05-05:00 EPA: empty tup_tail has noAnn In Parser.y, the tup_tail rule had the following option | {- empty -} %shift { return [Left noAnn] } Once this works through PostProcess.hs, it means we add an extra Missing constructor if the last item was a comma. Change the annotation type to a Bool to indicate this, and use the EpAnn Anchor for the print location for the others. - - - - - fa576eb8 by Andreas Klebinger at 2023-11-24T08:29:13-05:00 Fix FMA primops generating broken assembly on x86. `genFMA3Code` assumed that we had to take extra precations to avoid overwriting the result of `getNonClobberedReg`. One of these special cases caused a bug resulting in broken assembly. I believe we don't need to hadle these cases specially at all, which means this MR simply deletes the special cases to fix the bug. Fixes #24160 - - - - - 34d86315 by Alan Zimmerman at 2023-11-24T08:29:49-05:00 EPA: Remove parenthesizeHsType This is called from PostProcess.hs, and adds spurious parens. With the looser version of exact printing we had before we could tolerate this, as they would be swallowed by the original at the same place. But with the next change (remove EpAnnNotUsed) they result in duplicates in the output. For Darwin build: Metric Increase: MultiLayerModulesTH_OneShot - - - - - 3ede659d by Vladislav Zavialov at 2023-11-26T06:43:32-05:00 Add name for -Wdeprecated-type-abstractions (#24154) This warning had no name or flag and was triggered unconditionally. Now it is part of -Wcompat. - - - - - 7902ebf8 by Alan Zimmerman at 2023-11-26T06:44:08-05:00 EPA: Remove EpAnnNotUsed We no longer need the EpAnnNotUsed constructor for EpAnn, as we can represent an unused annotation with an anchor having a EpaDelta of zero, and empty comments and annotations. This simplifies code handling annotations considerably. Updates haddock submodule Metric Increase: parsing001 - - - - - 471b2672 by Mario Blažević at 2023-11-26T06:44:48-05:00 Bumped the upper bound of text to <2.2 - - - - - d1bf25c7 by Vladislav Zavialov at 2023-11-26T11:45:49-05:00 Term variable capture (#23740) This patch changes type variable lookup rules (lookupTypeOccRn) and implicit quantification rules (filterInScope) so that variables bound in the term namespace can be captured at the type level {-# LANGUAGE RequiredTypeArguments #-} f1 x = g1 @x -- `x` used in a type application f2 x = g2 (undefined :: x) -- `x` used in a type annotation f3 x = g3 (type x) -- `x` used in an embedded type f4 x = ... where g4 :: x -> x -- `x` used in a type signature g4 = ... This change alone does not allow us to accept examples shown above, but at least it gets them past the renamer. - - - - - da863d15 by Vladislav Zavialov at 2023-11-26T11:46:26-05:00 Update Note [hsScopedTvs and visible foralls] The Note was written before GHC gained support for visible forall in types of terms. Rewrite a few sentences and use a better example. - - - - - b5213542 by Matthew Pickering at 2023-11-27T12:53:59-05:00 testsuite: Add mechanism to collect generic metrics * Generalise the metric logic by adding an additional field which allows you to specify how to query for the actual value. Previously the method of querying the baseline value was abstracted (but always set to the same thing). * This requires rejigging how the stat collection works slightly but now it's more uniform and hopefully simpler. * Introduce some new "generic" helper functions for writing generic stats tests. - collect_size ( deviation, path ) Record the size of the file as a metric - stat_from_file ( metric, deviation, path ) Read a value from the given path, and store that as a metric - collect_generic_stat ( metric, deviation, get_stat) Provide your own `get_stat` function, `lambda way: <Int>`, which can be used to establish the current value of the metric. - collect_generic_stats ( metric_info ): Like collect_generic_stat but provide the whole dictionary of metric definitions. { metric: { deviation: <Int> current: lambda way: <Int> } } * Introduce two new "size" metrics for keeping track of build products. - `size_hello_obj` - The size of `hello.o` from compiling hello.hs - `libdir` - The total size of the `libdir` folder. * Track the number of modules in the AST tests - CountDepsAst - CountDepsParser This lays the infrastructure for #24191 #22256 #17129 - - - - - 7d9a2e44 by ARATA Mizuki at 2023-11-27T12:54:39-05:00 x86: Don't require -mavx2 when using 256-bit floating-point SIMD primitives Fixes #24222 - - - - - 4e5ff6a4 by Alan Zimmerman at 2023-11-27T12:55:15-05:00 EPA: Remove SrcSpanAnn Now that we only have a single constructor for EpAnn, And it uses a SrcSpan for its location, we can do away with SrcSpanAnn completely. It only existed to wrap the original SrcSpan in a location, and provide a place for the exact print annotation. For darwin only: Metric Increase: MultiLayerModulesTH_OneShot Updates haddock submodule - - - - - e05bca39 by Krzysztof Gogolewski at 2023-11-28T08:00:55-05:00 testsuite: don't initialize testdir to '.' The test directory is removed during cleanup, if there's an interrupt that could remove the entire repository. Fixes #24219 - - - - - af881674 by Alan Zimmerman at 2023-11-28T08:01:30-05:00 EPA: Clean up mkScope in Ast.hs Now that we have HasLoc we can get rid of all the custom variants of mkScope For deb10-numa Metric Increase: libdir - - - - - 292983c8 by Ben Gamari at 2023-11-28T22:44:28-05:00 distrib: Rediscover otool and install_name_tool on Darwin In the bindist configure script we must rediscover the `otool` and `install_name_tool`s since they may be different from the build environment. Fixes #24211. - - - - - dfe1c354 by Stefan Schulze Frielinghaus at 2023-11-28T22:45:04-05:00 llvmGen: Align objects in the data section Objects in the data section may be referenced via tagged pointers. Thus, align those objects to a 4- or 8-byte boundary for 32- or 64-bit platforms, respectively. Note, this may need to be reconsidered if objects with a greater natural alignment requirement are emitted as e.g. 128-bit atomics. Fixes #24163. - - - - - f6c486c3 by Matthew Pickering at 2023-11-29T11:08:13-05:00 metrics: Widen libdir and size_hello_obj acceptance window af8816740d9b8759be1a22af8adcb5f13edeb61d shows that the libdir size can fluctuate quite significantly even when the change is quite small. Therefore we widen the acceptance window to 10%. - - - - - 99a6a49c by Alan Zimmerman at 2023-11-29T11:08:49-05:00 EPA: Clean up TC Monad Utils We no longer need the alternative variant of addLocM (addLocMA) nor wrapLocAM, wrapLocSndMA. aarch64-darwin Metric Increase: MultiLayerModulesTH_OneShot deb10-numa-slow Metric Decrease: libdir - - - - - cbc03fa0 by Sebastian Graf at 2023-11-30T12:37:21-05:00 perf tests: Move comments into new `Note [Sensitivity to unique increment]` (#19414) And additionally to T12545, link from T8095, T13386 to this new Note. - - - - - c7623b22 by Alan Zimmerman at 2023-11-30T12:37:56-05:00 EPA: EpaDelta for comment has no comments EpaLocation is used to position things. It has two constructors, EpaSpan holding a SrcSpan, and EpaDelta with a delta position and a possible list of comments. The comment list is needed because the location in EpaDelta has no absolute information to decide which comments should be emitted before them when printing. But it is also used for specifying the position of a comment. To prevent the absurdity of a comment position having a list of comments in it, we make EpaLocation parameterisable, using comments for the normal case and a constant for within comments. Updates haddock submodule. aarch64-darwin Metric Decrease: MultiLayerModulesTH_OneShot - - - - - bd8acc0c by Krzysztof Gogolewski at 2023-11-30T12:38:32-05:00 Kind-check body of a required forall We now require that in 'forall a -> ty', ty has kind TYPE r for some r. Fixes #24176 - - - - - 010fb784 by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Remove incorrect haddock link quotes in code block - - - - - cda9c12d by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Remove cycle from group haddock example - - - - - 495265b9 by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Use repl haddock syntax in group docs - - - - - d134d1de by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Use list [] notation in group haddock - - - - - dfcf629c by Owen Shepherd at 2023-12-03T00:10:10-05:00 docs(NonEmpty/group): Specify final property of group function in haddock - - - - - cad3b734 by Owen Shepherd at 2023-12-03T00:10:10-05:00 fix: Add missing property of List.group - - - - - bad37656 by Matthew Pickering at 2023-12-03T00:10:46-05:00 testsuite: Fix T21097b test with make 4.1 (deb9) cee81370cd6ef256f66035e3116878d4cb82e28b recently added a test which failed on deb9 because the version of make was emitting the recipe failure to stdout rather than stderr. One way to fix this is to be more precise in the test about which part of the output we care about inspecting. - - - - - 5efdf421 by Matthew Pickering at 2023-12-03T00:11:21-05:00 testsuite: Track size of libdir in bytes For consistency it's better if we track all size metrics in bytes. Metric Increase: libdir - - - - - f5eb0f29 by Matthew Pickering at 2023-12-03T00:11:22-05:00 testsuite: Remove rogue trace in testsuite I accidentally left a trace in the generics metric patch. - - - - - d5610737 by Claudio Bley at 2023-12-06T16:13:33-05:00 Only exit ghci in -e mode when :add command fails Previously, when running `ghci -e ':add Sample.hs'` the process would exit with exit code 1 if the file exists and could be loaded. Fixes #24115 - - - - - 0f0c53a5 by Vladislav Zavialov at 2023-12-06T16:14:09-05:00 T2T in Patterns (#23739) This patch implements the T2T (term-to-type) transformation in patterns. Patterns that are checked against a visible forall can now be written without the `type` keyword: \(type t) (x :: t) -> ... -- old \t (x :: t) -> ... -- new The `t` binder is parsed and renamed as a term pattern (Pat), but then undergoes a conversion to a type pattern (HsTyPat). See the new function pat_to_type_pat in compiler/GHC/Tc/Gen/Pat.hs - - - - - 10a1a6c6 by Sebastian Graf at 2023-12-06T16:14:45-05:00 Pmc: Fix SrcLoc and warning for incomplete irrefutable pats (#24234) Before, the source location would point at the surrounding function definition, causing the confusion in #24234. I also took the opportunity to introduce a new `LazyPatCtx :: HsMatchContext _` to make the warning message say "irrefutable pattern" instead of "pattern binding". - - - - - 36b9a38c by Matthew Pickering at 2023-12-06T16:15:21-05:00 libraries: Bump filepath to 1.4.200.1 and unix to 2.8.4.0 Updates filepath submodule Updates unix submodule Fixes #24240 - - - - - 91ff0971 by Matthew Pickering at 2023-12-06T16:15:21-05:00 Submodule linter: Allow references to tags We modify the submodule linter so that if the bumped commit is a specific tag then the commit is accepted. Fixes #24241 - - - - - 86f652dc by Zubin Duggal at 2023-12-06T16:15:21-05:00 hadrian: set -Wno-deprecations for directory and Win32 The filepath bump to 1.4.200.1 introduces a deprecation warning. See https://gitlab.haskell.org/ghc/ghc/-/issues/24240 https://github.com/haskell/filepath/pull/206 - - - - - 7ac6006e by Sylvain Henry at 2023-12-06T16:16:02-05:00 Zap OccInfo on case binders during StgCse #14895 #24233 StgCse can revive dead binders: case foo of dead { Foo x y -> Foo x y; ... } ===> case foo of dead { Foo x y -> dead; ... } -- dead is no longer dead So we must zap occurrence information on case binders. Fix #14895 and #24233 - - - - - 57c391c4 by Sebastian Graf at 2023-12-06T16:16:37-05:00 Cpr: Turn an assertion into a check to deal with some dead code (#23862) See the new `Note [Dead code may contain type confusions]`. Fixes #23862. - - - - - c1c8abf8 by Zubin Duggal at 2023-12-08T02:25:07-05:00 testsuite: add test for #23944 - - - - - 6329d308 by Zubin Duggal at 2023-12-08T02:25:07-05:00 driver: Only run a dynamic-too pipeline if object files are going to be generated Otherwise we run into a panic in hscMaybeWriteIface: "Unexpected DT_Dyn state when writing simple interface" when dynamic-too is enabled We could remove the panic and just write the interface even if the state is `DT_Dyn`, but it seems pointless to run the pipeline twice when `hscMaybeWriteIface` is already designed to write both `hi` and `dyn_hi` files if dynamic-too is enabled. Fixes #23944. - - - - - 28811f88 by Simon Peyton Jones at 2023-12-08T05:47:18-05:00 Improve duplicate elimination in SpecConstr This partially fixes #24229. See the new Note [Pattern duplicate elimination] in SpecConstr - - - - - fec7894f by Simon Peyton Jones at 2023-12-08T05:47:18-05:00 Make SpecConstr deal with casts better This patch does two things, to fix #23209: * It improves SpecConstr so that it no longer quantifies over coercion variables. See Note [SpecConstr and casts] * It improves the rule matcher to deal nicely with the case where the rule does not quantify over coercion variables, but the the template has a cast in it. See Note [Casts in the template] - - - - - 8db8d2fd by Zubin Duggal at 2023-12-08T05:47:54-05:00 driver: Don't lose track of nodes when we fail to resolve cycles The nodes that take part in a cycle should include both hs-boot and hs files, but when we fail to resolve a cycle, we were only counting the nodes from the graph without boot files. Fixes #24196 - - - - - c5b4efd3 by Zubin Duggal at 2023-12-08T05:48:30-05:00 testsuite: Skip MultiLayerModulesTH_OneShot on darwin See #24177 - - - - - fae472a9 by Wendao Lee at 2023-12-08T05:49:12-05:00 docs(Data.Char):Add more detailed descriptions for some functions Related changed function's docs: -GHC.Unicode.isAlpha -GHC.Unicode.isPrint -GHC.Unicode.isAlphaNum Add more details for what the function will return. Co-authored-by: Bodigrim <andrew.lelechenko at gmail.com> - - - - - ca7510e4 by Malik Ammar Faisal at 2023-12-08T05:49:55-05:00 Fix float parsing in GHC Cmm Lexer Add test case for bug #24224 - - - - - d8baa1bd by Simon Peyton Jones at 2023-12-08T15:40:37+00:00 Take care when simplifying unfoldings This MR fixes a very subtle bug exposed by #24242. See Note [Environment for simplLetUnfolding]. I also updated a bunch of Notes on shadowing - - - - - 03ca551d by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Comments only in FloatIn Relevant to #3458 - - - - - 50c78779 by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Comments only in SpecConstr - - - - - 9431e195 by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Add test for #22238 - - - - - d9e4c597 by Vladislav Zavialov at 2023-12-11T04:19:34-05:00 Make forall a keyword (#23719) Before this change, GHC used to accept `forall` as a term-level identifier: -- from constraints-0.13 forall :: forall p. (forall a. Dict (p a)) -> Dict (Forall p) forall d = ... Now it is a parse error. The -Wforall-identifier warning has served its purpose and is now a deprecated no-op. - - - - - 58d56644 by Zubin Duggal at 2023-12-11T04:20:10-05:00 driver: Ensure we actually clear the interactive context before reloading Previously we called discardIC, but immediately after set the session back to an old HscEnv that still contained the IC Partially addresses #24107 Fixes #23405 - - - - - 8e5745a0 by Zubin Duggal at 2023-12-11T04:20:10-05:00 driver: Ensure we force the lookup of old build artifacts before returning the build plan This prevents us from retaining all previous build artifacts in memory until a recompile finishes, instead only retaining the exact artifacts we need. Fixes #24118 - - - - - 105c370c by Zubin Duggal at 2023-12-11T04:20:10-05:00 testsuite: add test for #24118 and #24107 MultiLayerModulesDefsGhci was not able to catch the leak because it uses :l which discards the previous environment. Using :r catches both of these leaks - - - - - e822ff88 by Zubin Duggal at 2023-12-11T04:20:10-05:00 compiler: Add some strictness annotations to ImportSpec and related constructors This prevents us from retaining entire HscEnvs. Force these ImportSpecs when forcing the GlobalRdrEltX Adds an NFData instance for Bag Fixes #24107 - - - - - 522c12a4 by Zubin Duggal at 2023-12-11T04:20:10-05:00 compiler: Force IfGlobalRdrEnv in NFData instance. - - - - - 188b280d by Arnaud Spiwack at 2023-12-11T15:33:31+01:00 LinearTypes => MonoLocalBinds - - - - - 8e0446df by Arnaud Spiwack at 2023-12-11T15:44:28+01:00 Linear let and where bindings For expediency, the initial implementation of linear types in GHC made it so that let and where binders would always be considered unrestricted. This was rather unpleasant, and probably a big obstacle to adoption. At any rate, this was not how the proposal was designed. This patch fixes this infelicity. It was surprisingly difficult to build, which explains, in part, why it took so long to materialise. As of this patch, let or where bindings marked with %1 will be linear (respectively %p for an arbitrary multiplicity p). Unmarked let will infer their multiplicity. Here is a prototypical example of program that used to be rejected and is accepted with this patch: ```haskell f :: A %1 -> B g :: B %1 -> C h :: A %1 -> C h x = g y where y = f x ``` Exceptions: - Recursive let are unrestricted, as there isn't a clear semantics of what a linear recursive binding would be. - Destructive lets with lazy bindings are unrestricted, as their desugaring isn't linear (see also #23461). - (Strict) destructive lets with inferred polymorphic type are unrestricted. Because the desugaring isn't linear (See #18461 down-thread). Closes #18461 and #18739 Co-authored-by: @jackohughes - - - - - effa7e2d by Matthew Craven at 2023-12-12T04:37:20-05:00 Introduce `dataToTagSmall#` primop (closes #21710) ...and use it to generate slightly better code when dataToTag# is used at a "small data type" where there is no need to mess with "is_too_big_tag" or potentially look at an info table. Metric Decrease: T18304 - - - - - 35c7aef6 by Matthew Craven at 2023-12-12T04:37:20-05:00 Fix formatting of Note [alg-alt heap check] - - - - - 7397c784 by Oleg Grenrus at 2023-12-12T04:37:56-05:00 Allow untyped brackets in typed splices and vice versa. Resolves #24190 Apparently the check was essentially always (as far as I can trace back: d0d47ba76f8f0501cf3c4966bc83966ab38cac27), and while it does catch some mismatches, the type-checker will catch them too. OTOH, it prevents writing completely reasonable programs. - - - - - a3ee3b99 by Moritz Angermann at 2023-12-12T19:50:58-05:00 Drop hard Xcode dependency XCODE_VERSION calls out to `xcodebuild`, which is only available when having `Xcode` installed. The CommandLineTools are not sufficient. To install Xcode, you must have an apple id to download the Xcode.xip from apple. We do not use xcodebuild anywhere in our build explicilty. At best it appears to be a proxy for checking the linker or the compiler. These should rather be done with ``` xcrun ld -version ``` or similar, and not by proxy through Xcode. The CLR should be sufficient for building software on macOS. - - - - - 1c9496e0 by Vladislav Zavialov at 2023-12-12T19:51:34-05:00 docs: update information on RequiredTypeArguments Update the User's Guide and Release Notes to account for the recent progress in the implementation of RequiredTypeArguments. - - - - - d0b17576 by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Fix off-by-one in assertion Previously we failed to account for the NULL terminator `postString` asserted that there is enough room in the buffer for the string. - - - - - a10f9b9b by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Honor result of ensureRoomForVariableEvent is Previously we would keep plugging along, even if isn't enough room for the event. - - - - - 0e0f41c0 by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Avoid truncating event sizes Previously ensureRoomForVariableEvent would truncate the desired size to 16-bits, resulting in #24197. Fixes #24197. - - - - - 64e724c8 by Artin Ghasivand at 2023-12-13T06:34:20-05:00 Remove the "Derived Constraint" argument of TcPluginSolver, docs - - - - - fe6d97dd by Vladislav Zavialov at 2023-12-13T06:34:56-05:00 EPA: Move tokens into GhcPs extension fields (#23447) Summary of changes * Remove Language.Haskell.Syntax.Concrete * Move all tokens into GhcPs extension fields (LHsToken -> EpToken) * Create new TTG extension fields as needed * Drop the MultAnn wrapper Updates the haddock submodule. Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 8106e695 by Zubin Duggal at 2023-12-13T06:35:34-05:00 testsuite: use copy_files in T23405 This prevents the tree from being dirtied when the file is modified. - - - - - ed0e4099 by Bryan Richter at 2023-12-14T04:30:53-05:00 Document ghc package's PVP-noncompliance This changes nothing, it just makes the status quo explicit. - - - - - 8bef8d9f by Luite Stegeman at 2023-12-14T04:31:33-05:00 JS: Mark spurious CI failures js_fragile(24259) This marks the spurious test failures on the JS platform as js_fragile(24259), so we don't hold up merge requests while fixing the underlying issues. See #24259 - - - - - 1c79526a by Finley McIlwaine at 2023-12-15T12:24:40-08:00 Late plugins - - - - - 000c3302 by Finley McIlwaine at 2023-12-15T12:24:40-08:00 withTiming on LateCCs and late plugins - - - - - be4551ac by Finley McIlwaine at 2023-12-15T12:24:40-08:00 add test for late plugins - - - - - 7c29da9f by Finley McIlwaine at 2023-12-15T12:24:40-08:00 Document late plugins - - - - - 9a52ae46 by Ben Gamari at 2023-12-20T07:07:26-05:00 Fix thunk update ordering Previously we attempted to ensure soundness of concurrent thunk update by synchronizing on the access of the thunk's info table pointer field. This was believed to be sufficient since the indirectee (which may expose a closure allocated by another core) would not be examined until the info table pointer update is complete. However, it turns out that this can result in data races in the presence of multiple threads racing a update a single thunk. For instance, consider this interleaving under the old scheme: Thread A Thread B --------- --------- t=0 Enter t 1 Push update frame 2 Begin evaluation 4 Pause thread 5 t.indirectee=tso 6 Release t.info=BLACKHOLE 7 ... (e.g. GC) 8 Resume thread 9 Finish evaluation 10 Relaxed t.indirectee=x 11 Load t.info 12 Acquire fence 13 Inspect t.indirectee 14 Release t.info=BLACKHOLE Here Thread A enters thunk `t` but is soon paused, resulting in `t` being lazily blackholed at t=6. Then, at t=10 Thread A finishes evaluation and updates `t.indirectee` with a relaxed store. Meanwhile, Thread B enters the blackhole. Under the old scheme this would introduce an acquire-fence but this would only synchronize with Thread A at t=6. Consequently, the result of the evaluation, `x`, is not visible to Thread B, introducing a data race. We fix this by treating the `indirectee` field as we do all other mutable fields. This means we must always access this field with acquire-loads and release-stores. See #23185. - - - - - f4b53538 by Vladislav Zavialov at 2023-12-20T07:08:02-05:00 docs: Fix link to 051-ghc-base-libraries.rst The proposal is no longer available at the previous URL. - - - - - f7e21fab by Matthew Pickering at 2023-12-21T14:57:40+00:00 hadrian: Build all executables in bin/ folder In the end the bindist creation logic copies them all into the bin folder. There is no benefit to building a specific few binaries in the lib/bin folder anymore. This also removes the ad-hoc logic to copy the touchy and unlit executables from stage0 into stage1. It takes <1s to build so we might as well just build it. - - - - - 0038d052 by Zubin Duggal at 2023-12-22T23:28:00-05:00 testsuite: mark jspace as fragile on i386. This test has been flaky for some time and has been failing consistently on i386-linux since 8e0446df landed. See #24261 - - - - - dfd670a0 by Ben Bellick at 2023-12-24T10:10:31-05:00 Deprecate -ddump-json and introduce -fdiagnostics-as-json Addresses #19278 This commit deprecates the underspecified -ddump-json flag and introduces a newer, well-specified flag -fdiagnostics-as-json. Also included is a JSON schema as part of the documentation. The -ddump-json flag will be slated for removal shortly after this merge. - - - - - 609e6225 by Ben Bellick at 2023-12-24T10:10:31-05:00 Deprecate -ddump-json and introduce -fdiagnostics-as-json Addresses #19278 This commit deprecates the underspecified -ddump-json flag and introduces a newer, well-specified flag -fdiagnostics-as-json. Also included is a JSON schema as part of the documentation. The -ddump-json flag will be slated for removal shortly after this merge. - - - - - 865513b2 by Ömer Sinan Ağacan at 2023-12-24T10:11:13-05:00 Fix BNF in user manual 6.6.8.2: formal syntax for instance declarations - - - - - c247b6be by Zubin Duggal at 2023-12-25T16:01:23-05:00 docs: document permissibility of -XOverloadedLabels (#24249) Document the permissibility introduced by https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0170-unrestricted-overloadedlabels.rst - - - - - e5b7eb59 by Ömer Sinan Ağacan at 2023-12-25T16:02:03-05:00 Fix a code block syntax in user manual sec. 6.8.8.6 - - - - - 2db11c08 by Ben Gamari at 2023-12-29T15:35:48-05:00 genSym: Reimplement via CAS on 32-bit platforms Previously the remaining use of the C implementation on 32-bit platforms resulted in a subtle bug, #24261. This was due to the C object (which used the RTS's `atomic_inc64` macro) being compiled without `-threaded` yet later being used in a threaded compiler. Side-step this issue by using the pure Haskell `genSym` implementation on all platforms. This required implementing `fetchAddWord64Addr#` in terms of CAS on 64-bit platforms. - - - - - 19328a8c by Xiaoyan Ren at 2023-12-29T15:36:30-05:00 Do not color the diagnostic code in error messages (#24172) - - - - - 685b467c by Krzysztof Gogolewski at 2023-12-29T15:37:06-05:00 Enforce that bindings of implicit parameters are lifted Fixes #24298 - - - - - bc4d67b7 by Matthew Craven at 2023-12-31T06:15:42-05:00 StgToCmm: Detect some no-op case-continuations ...and generate no code for them. Fixes #24264. - - - - - 5b603139 by Krzysztof Gogolewski at 2023-12-31T06:16:18-05:00 Revert "testsuite: mark jspace as fragile on i386." This reverts commit 0038d052c8c80b4b430bb2aa1c66d5280be1aa95. The atomicity bug should be fixed by !11802. - - - - - d55216ad by Krzysztof Gogolewski at 2024-01-01T12:05:49-05:00 Refactor: store [[PrimRep]] rather than [Type] in STG StgConApp stored a list of types. This list was used exclusively during unarisation of unboxed sums (mkUbxSum). However, this is at a wrong level of abstraction: STG shouldn't be concerned with Haskell types, only PrimReps. Update the code to store a [[PrimRep]]. Also, there's no point in storing this list when we're not dealing with an unboxed sum. - - - - - 8b340bc7 by Ömer Sinan Ağacan at 2024-01-01T12:06:29-05:00 Kind signatures docs: mention that they're allowed in newtypes - - - - - 989bf8e5 by Zubin Duggal at 2024-01-03T20:08:47-05:00 ci: Ensure we use the correct bindist name for the test artifact when generating release ghcup metadata Fixes #24268 - - - - - 89299a89 by Krzysztof Gogolewski at 2024-01-03T20:09:23-05:00 Refactor: remove calls to typePrimRepArgs The function typePrimRepArgs is just a thin wrapper around typePrimRep, adding a VoidRep if the list is empty. However, in StgToByteCode, we were discarding that VoidRep anyway, so there's no point in calling it. - - - - - c7be0c68 by mmzk1526 at 2024-01-03T20:10:07-05:00 Use "-V" for alex version check for better backward compatibility Fixes #24302. In recent versions of alex, "-v" is used for "--verbose" instead of "-version". - - - - - 67dbcc0a by Krzysztof Gogolewski at 2024-01-05T02:07:18-05:00 Fix VoidRep handling in ghci debugger 'go' inside extractSubTerms was giving a bad result given a VoidRep, attempting to round towards the next multiple of 0. I don't understand much about the debugger but the code should be better than it was. Fixes #24306 - - - - - 90ea574e by Krzysztof Gogolewski at 2024-01-05T02:07:54-05:00 VoidRep-related refactor * In GHC.StgToByteCode, replace bcIdPrimId with idPrimRep, bcIdArgRep with idArgRep, atomPrimRep with stgArgRep1. All of them were duplicates. * In GHC.Stg.Unarise, we were converting a PrimRep to a Type and back to PrimRep. Remove the calls to primRepToType and typePrimRep1 which cancel out. * In GHC.STG.Lint, GHC.StgToCmm, GHC.Types.RepType we were filtering out VoidRep from the result of typePrimRep. But typePrimRep never returns VoidRep - remove the filtering. - - - - - eaf72479 by brian at 2024-01-06T23:03:09-05:00 Add unaligned Addr# primops Implements CLC proposal #154: https://github.com/haskell/core-libraries-committee/issues/154 * add unaligned addr primops * add tests * accept tests * add documentation * fix js primops * uncomment in access ops * use Word64 in tests * apply suggestions * remove extra file * move docs * remove random options * use setByteArray# primop * better naming * update base-exports test * add base-exports for other architectures - - - - - d471d445 by Krzysztof Gogolewski at 2024-01-06T23:03:47-05:00 Remove VoidRep from PrimRep, introduce PrimOrVoidRep This introduces data PrimOrVoidRep = VoidRep | NVRep PrimRep changes typePrimRep1 to return PrimOrVoidRep, and adds a new function typePrimRepU to be used when the argument is definitely non-void. Details in Note [VoidRep] in GHC.Types.RepType. Fixes #19520 - - - - - 48720a07 by Matthew Craven at 2024-01-08T18:57:36-05:00 Apply Note [Sensitivity to unique increment] to LargeRecord - - - - - 9e2e180f by Sebastian Graf at 2024-01-08T18:58:13-05:00 Debugging: Add diffUFM for convenient diffing between UniqFMs - - - - - 948f3e35 by Sebastian Graf at 2024-01-08T18:58:13-05:00 Rename Opt_D_dump_stranal to Opt_D_dump_dmdanal ... and Opt_D_dump_str_signatures to Opt_D_dump_dmd_signatures - - - - - 4e217e3e by Sebastian Graf at 2024-01-08T18:58:13-05:00 Deprecate -ddump-stranal and -ddump-str-signatures ... and suggest -ddump-dmdanal and -ddump-dmd-signatures instead - - - - - 6c613c90 by Sebastian Graf at 2024-01-08T18:58:13-05:00 Move testsuite/tests/stranal to testsuite/tests/dmdanal A separate commit so that the rename is obvious to Git(Lab) - - - - - c929f02b by Sebastian Graf at 2024-01-08T18:58:13-05:00 CoreSubst: Stricten `substBndr` and `cloneBndr` Doing so reduced allocations of `cloneBndr` by about 25%. ``` T9233(normal) ghc/alloc 672,488,656 663,083,216 -1.4% GOOD T9675(optasm) ghc/alloc 423,029,256 415,812,200 -1.7% geo. mean -0.1% minimum -1.7% maximum +0.1% ``` Metric Decrease: T9233 - - - - - e3ca78f3 by Krzysztof Gogolewski at 2024-01-10T17:35:59-05:00 Deprecate -Wsemigroup This warning was used to prepare for Semigroup becoming a superclass of Monoid, and for (<>) being exported from Prelude. This happened in GHC 8.4 in 8ae263ceb3566 and feac0a3bc69fd3. The leftover logic for (<>) has been removed in GHC 9.8, 4d29ecdfcc79. Now the warning does nothing at all and can be deprecated. - - - - - 08d14925 by amesgen at 2024-01-10T17:36:42-05:00 WASM metadata: use correct GHC version - - - - - 7a808419 by Xiaoyan Ren at 2024-01-10T17:37:24-05:00 Allow SCC declarations in TH (#24081) - - - - - 28827c51 by Xiaoyan Ren at 2024-01-10T17:37:24-05:00 Fix prettyprinting of SCC pragmas - - - - - ae9cc1a8 by Matthew Craven at 2024-01-10T17:38:01-05:00 Fix loopification in the presence of void arguments This also removes Note [Void arguments in self-recursive tail calls], which was just misleading. It's important to count void args both in the function's arity and at the call site. Fixes #24295. - - - - - b718b145 by Zubin Duggal at 2024-01-10T17:38:36-05:00 testsuite: Teach testsuite driver about c++ sources - - - - - 09cb57ad by Zubin Duggal at 2024-01-10T17:38:36-05:00 driver: Set -DPROFILING when compiling C++ sources with profiling Earlier, we used to pass all preprocessor flags to the c++ compiler. This meant that -DPROFILING was passed to the c++ compiler because it was a part of C++ flags However, this was incorrect and the behaviour was changed in 8ff3134ed4aa323b0199ad683f72165e51a59ab6. See #21291. But that commit exposed this bug where -DPROFILING was no longer being passed when compiling c++ sources. The fix is to explicitly include -DPROFILING in `opt_cxx` when profiling is enabled to ensure we pass the correct options for the way to both C and C++ compilers Fixes #24286 - - - - - 2cf9dd96 by Zubin Duggal at 2024-01-10T17:38:36-05:00 testsuite: rename objcpp -> objcxx To avoid confusion with C Pre Processsor - - - - - af6932d6 by Simon Peyton Jones at 2024-01-10T17:39:12-05:00 Make TYPE and CONSTRAINT not-apart Issue #24279 showed up a bug in the logic in GHC.Core.Unify.unify_ty which is supposed to make TYPE and CONSTRAINT be not-apart. Easily fixed. - - - - - 4a39b5ff by Zubin Duggal at 2024-01-10T17:39:48-05:00 ci: Fix typo in mk_ghcup_metadata.py There was a missing colon in the fix to #24268 in 989bf8e53c08eb22de716901b914b3607bc8dd08 - - - - - 13503451 by Zubin Duggal at 2024-01-10T17:40:24-05:00 release-ci: remove release-x86_64-linux-deb11-release+boot_nonmoving_gc job There is no reason to have this release build or distribute this variation. This configuration is for testing purposes only. - - - - - afca46a4 by Sebastian Graf at 2024-01-10T17:41:00-05:00 Parser: Add a Note detailing why we need happy's `error` to implement layout - - - - - eaf8a06d by Krzysztof Gogolewski at 2024-01-11T00:43:17+01:00 Turn -Wtype-equality-out-of-scope on by default Also remove -Wnoncanonical-{monoid,monad}-instances from -Wcompat, since they are enabled by default. Refresh wcompat-warnings/ test with new -Wcompat warnings. Part of #24267 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 42bee5aa by Sebastian Graf at 2024-01-12T21:16:21-05:00 Arity: Require called *exactly once* for eta exp with -fpedantic-bottoms (#24296) In #24296, we had a program in which we eta expanded away an error despite the presence of `-fpedantic-bottoms`. This was caused by turning called *at least once* lambdas into one-shot lambdas, while with `-fpedantic-bottoms` it is only sound to eta expand over lambdas that are called *exactly* once. An example can be found in `Note [Combining arity type with demand info]`. Fixes #24296. - - - - - 7e95f738 by Andreas Klebinger at 2024-01-12T21:16:57-05:00 Aarch64: Enable -mfma by default. Fixes #24311 - - - - - e43788d0 by Jason Shipman at 2024-01-14T12:47:38-05:00 Add more instances for Compose: Fractional, RealFrac, Floating, RealFloat CLC proposal #226 https://github.com/haskell/core-libraries-committee/issues/226 - - - - - ae6d8cd2 by Sebastian Graf at 2024-01-14T12:48:15-05:00 Pmc: COMPLETE pragmas associated with Family TyCons should apply to representation TyCons as well (#24326) Fixes #24326. - - - - - c5fc7304 by sheaf at 2024-01-15T14:15:29-05:00 Use lookupOccRn_maybe in TH.lookupName When looking up a value, we want to be able to find both variables and record fields. So we should not use the lookupSameOccRn_maybe function, as we can't know ahead of time which record field namespace a record field with the given textual name will belong to. Fixes #24293 - - - - - da908790 by Krzysztof Gogolewski at 2024-01-15T14:16:05-05:00 Make the build more strict on documentation errors * Detect undefined labels. This can be tested by adding :ref:`nonexistent` to a documentation rst file; attempting to build docs will fail. Fixed the undefined label in `9.8.1-notes.rst`. * Detect errors. While we have plenty of warnings, we can at least enforce that Sphinx does not report errors. Fixed the error in `required_type_arguments.rst`. Unrelated change: I have documented that the `-dlint` enables `-fcatch-nonexhaustive-cases`, as can be verified by checking `enableDLint`. - - - - - 5077416e by Javier Sagredo at 2024-01-16T15:40:06-05:00 Profiling: Adds an option to not start time profiling at startup Using the functionality provided by d89deeba47ce04a5198a71fa4cbc203fe2c90794, this patch creates a new rts flag `--no-automatic-time-samples` which disables the time profiling when starting a program. It is then expected that the user starts it whenever it is needed. Fixes #24337 - - - - - 5776008c by Matthew Pickering at 2024-01-16T15:40:42-05:00 eventlog: Fix off-by-one error in postIPE We were missing the extra_comma from the calculation of the size of the payload of postIPE. This was causing assertion failures when the event would overflow the buffer by one byte, as ensureRoomForVariable event would report there was enough space for `n` bytes but then we would write `n + 1` bytes into the buffer. Fixes #24287 - - - - - 66dc09b1 by Simon Peyton Jones at 2024-01-16T15:41:18-05:00 Improve SpecConstr (esp nofib/spectral/ansi) This MR makes three improvements to SpecConstr: see #24282 * It fixes an outright (and recently-introduced) bug in `betterPat`, which was wrongly forgetting to compare the lengths of the argument lists. * It enhances ConVal to inclue a boolean for work-free-ness, so that the envt can contain non-work-free constructor applications, so that we can do more: see Note [ConVal work-free-ness] * It rejigs `subsumePats` so that it doesn't reverse the list. This can make a difference because, when patterns overlap, we arbitrarily pick the first. There is no "right" way, but this retains the old pre-subsumePats behaviour, thereby "fixing" the regression in #24282. Nofib results +======================================== | spectral/ansi -21.14% | spectral/hartel/comp_lab_zift -0.12% | spectral/hartel/parstof +0.09% | spectral/last-piece -2.32% | spectral/multiplier +6.03% | spectral/para +0.60% | spectral/simple -0.26% +======================================== | geom mean -0.18% +---------------------------------------- The regression in `multiplier` is sad, but it simply replicates GHC's previous behaviour (e.g. GHC 9.6). - - - - - 65da79b3 by Matthew Pickering at 2024-01-16T15:41:54-05:00 hadrian: Reduce Cabal verbosity The comment claims that `simpleUserHooks` decrease verbosity, and it does, but only for the `postConf` phase. The other phases are too verbose with `-V`. At the moment > 5000 lines of the build log are devoted to output from `cabal copy`. So I take the simple approach and just decrease the verbosity level again. If the output of `postConf` is essential then it would be better to implement our own `UserHooks` which doesn't decrease the verbosity for `postConf`. Fixes #24338 - - - - - 16414d7d by Matthew Pickering at 2024-01-17T10:54:59-05:00 Stop retaining old ModGuts throughout subsequent simplifier phases Each phase of the simplifier typically rewrites the majority of ModGuts, so we want to be able to release the old ModGuts as soon as possible. `name_ppr_ctxt` lives throught the whole optimiser phase and it was retaining a reference to `ModGuts`, so we were failing to release the old `ModGuts` until the end of the phase (potentially doubling peak memory usage for that particular phase). This was discovered using eras profiling (#24332) Fixes #24328 - - - - - 7f0879e1 by Matthew Pickering at 2024-01-17T10:55:35-05:00 Update nofib submodule - - - - - 320454d3 by Cheng Shao at 2024-01-17T23:02:40+00:00 ci: bump ci-images for updated wasm image - - - - - 2eca52b4 by Cheng Shao at 2024-01-17T23:06:44+00:00 base: treat all FDs as "nonblocking" on wasm On posix platforms, when performing read/write on FDs, we check the nonblocking flag first. For FDs without this flag (e.g. stdout), we call fdReady() first, which in turn calls poll() to wait for I/O to be available on that FD. This is problematic for wasm32-wasi: although select()/poll() is supported via the poll_oneoff() wasi syscall, that syscall is rather heavyweight and runtime behavior differs in different wasi implementations. The issue is even worse when targeting browsers, given there's no satisfactory way to implement async I/O as a synchronous syscall, so existing JS polyfills for wasi often give up and simply return ENOSYS. Before we have a proper I/O manager that avoids poll_oneoff() for async I/O on wasm, this patch improves the status quo a lot by merely pretending all FDs are "nonblocking". Read/write on FDs will directly invoke read()/write(), which are much more reliably handled in existing wasi implementations, especially those in browsers. Fixes #23275 and the following test cases: T7773 isEOF001 openFile009 T4808 cgrun025 Approved by CLC proposal #234: https://github.com/haskell/core-libraries-committee/issues/234 - - - - - 83c6c710 by Andrew Lelechenko at 2024-01-18T05:21:49-05:00 base: clarify how to disable warnings about partiality of Data.List.{head,tail} - - - - - c4078f2f by Simon Peyton Jones at 2024-01-18T05:22:25-05:00 Fix four bug in handling of (forall cv. body_ty) These bugs are all described in #24335 It's not easy to provoke the bug, hence no test case. - - - - - 119586ea by Alexis King at 2024-01-19T00:08:00-05:00 Always refresh profiling CCSes after running pending initializers Fixes #24171. - - - - - 9718d970 by Oleg Grenrus at 2024-01-19T00:08:36-05:00 Set default-language: GHC2021 in ghc library Go through compiler/ sources, and remove all BangPatterns (and other GHC2021 enabled extensions in these files). - - - - - 3ef71669 by Matthew Pickering at 2024-01-19T21:55:16-05:00 testsuite: Remove unused have_library function Also remove the hence unused testsuite option `--test-package-db`. Fixes #24342 - - - - - 5b7fa20c by Jade at 2024-01-19T21:55:53-05:00 Fix Spelling in the compiler Tracking: #16591 - - - - - 09875f48 by Matthew Pickering at 2024-01-20T12:20:44-05:00 testsuite: Implement `isInTreeCompiler` in a more robust way Just a small refactoring to avoid redundantly specifying the same strings in two different places. - - - - - 0d12b987 by Jade at 2024-01-20T12:21:20-05:00 Change maintainer email from cvs-ghc at haskell.org to ghc-devs at haskell.org. Fixes #22142 - - - - - 1fa1c00c by Jade at 2024-01-23T19:17:03-05:00 Enhance Documentation of functions exported by Data.Function This patch aims to improve the documentation of functions exported in Data.Function Tracking: #17929 Fixes: #10065 - - - - - ab47a43d by Jade at 2024-01-23T19:17:39-05:00 Improve documentation of hGetLine. - Add explanation for whether a newline is returned - Add examples Fixes #14804 - - - - - dd4af0e5 by Cheng Shao at 2024-01-23T19:18:17-05:00 Fix genapply for cross-compilation by nuking fragile CPP logic This commit fixes incorrectly built genapply when cross compiling (#24347) by nuking all fragile CPP logic in it from the orbit. All target-specific info are now read from DerivedConstants.h at runtime, see added note for details. Also removes a legacy Makefile and adds haskell language server support for genapply. - - - - - 0cda2b8b by Cheng Shao at 2024-01-23T19:18:17-05:00 rts: enable wasm32 register mapping The wasm backend didn't properly make use of all Cmm global registers due to #24347. Now that it is fixed, this patch re-enables full register mapping for wasm32, and we can now generate smaller & faster wasm modules that doesn't always spill arguments onto the stack. Fixes #22460 #24152. - - - - - 0325a6e5 by Greg Steuck at 2024-01-24T01:29:44-05:00 Avoid utf8 in primops.txt.pp comments They don't make it through readFile' without explicitly setting the encoding. See https://gitlab.haskell.org/ghc/ghc/-/issues/17755 - - - - - 1aaf0bd8 by David Binder at 2024-01-24T01:30:20-05:00 Bump hpc and hpc-bin submodule Bump hpc to 0.7.0.1 Bump hpc-bin to commit d1780eb2 - - - - - e693a4e8 by Ben Gamari at 2024-01-24T01:30:56-05:00 testsuite: Ignore stderr in T8089 Otherwise spurious "Killed: 9" messages to stderr may cause the test to fail. Fixes #24361. - - - - - a40f4ab2 by sheaf at 2024-01-24T14:04:33-05:00 Fix FMA instruction on LLVM We were emitting the wrong instructions for fused multiply-add operations on LLVM: - the instruction name is "llvm.fma.f32" or "llvm.fma.f64", not "fmadd" - LLVM does not support other instructions such as "fmsub"; instead we implement these by flipping signs of some arguments - the instruction is an LLVM intrinsic, which requires handling it like a normal function call instead of a machine instruction Fixes #24223 - - - - - 69abc786 by Andrei Borzenkov at 2024-01-24T14:05:09-05:00 Add changelog entry for renaming tuples from (,,...,,) to Tuple<n> (24291) - - - - - 0ac8f385 by Cheng Shao at 2024-01-25T00:27:48-05:00 compiler: remove unused GHC.Linker module The GHC.Linker module is empty and unused, other than as a hack for the make build system. We can remove it now that make is long gone; the note is moved to GHC.Linker.Loader instead. - - - - - 699da01b by Hécate Moonlight at 2024-01-25T00:28:27-05:00 Clarification for newtype constructors when using `coerce` - - - - - b2d8cd85 by Matt Walker at 2024-01-26T09:50:08-05:00 Fix #24308 Add tests for semicolon separated where clauses - - - - - 0da490a1 by Ben Gamari at 2024-01-26T17:34:41-05:00 hsc2hs: Bump submodule - - - - - 3f442fd2 by Ben Gamari at 2024-01-26T17:34:41-05:00 Bump containers submodule to 0.7 - - - - - 82a1c656 by Sebastian Nagel at 2024-01-29T02:32:40-05:00 base: with{Binary}File{Blocking} only annotates own exceptions Fixes #20886 This ensures that inner, unrelated exceptions are not misleadingly annotated with the opened file. - - - - - 9294a086 by Andreas Klebinger at 2024-01-29T02:33:15-05:00 Fix fma warning when using llvm on aarch64. On aarch64 fma is always on so the +fma flag doesn't exist for that target. Hence no need to try and pass +fma to llvm. Fixes #24379 - - - - - ced2e731 by sheaf at 2024-01-29T17:27:12-05:00 No shadowing warnings for NoFieldSelector fields This commit ensures we don't emit shadowing warnings when a user shadows a field defined with NoFieldSelectors. Fixes #24381 - - - - - 8eeadfad by Patrick at 2024-01-29T17:27:51-05:00 Fix bug wrong span of nested_doc_comment #24378 close #24378 1. Update the start position of span in `nested_doc_comment` correctly. and hence the spans of identifiers of haddoc can be computed correctly. 2. add test `HaddockSpanIssueT24378`. - - - - - a557580f by Alexey Radkov at 2024-01-30T19:41:52-05:00 Fix irrelevant dodgy-foreign-imports warning on import f-pointers by value A test *сс018* is attached (not sure about the naming convention though). Note that without the fix, the test fails with the *dodgy-foreign-imports* warning passed to stderr. The warning disappears after the fix. GHC shouldn't warn on imports of natural function pointers from C by value (which is feasible with CApiFFI), such as ```haskell foreign import capi "cc018.h value f" f :: FunPtr (Int -> IO ()) ``` where ```c void (*f)(int); ``` See a related real-world use-case [here](https://gitlab.com/daniel-casanueva/pcre-light/-/merge_requests/17). There, GHC warns on import of C function pointer `pcre_free`. - - - - - ca99efaf by Alexey Radkov at 2024-01-30T19:41:53-05:00 Rename test cc018 -> T24034 - - - - - 88c38dd5 by Ben Gamari at 2024-01-30T19:42:28-05:00 rts/TraverseHeap.c: Ensure that PosixSource.h is included first - - - - - ca2e919e by Simon Peyton Jones at 2024-01-31T09:29:45+00:00 Make decomposeRuleLhs a bit more clever This fixes #24370 by making decomposeRuleLhs undertand dictionary /functions/ as well as plain /dictionaries/ - - - - - 94ce031d by Teo Camarasu at 2024-02-01T05:49:49-05:00 doc: Add -Dn flag to user guide Resolves #24394 - - - - - b2285cf4 by Matthew Craven at 2024-02-01T12:23:19-05:00 Bump bytestring submodule to upstream HEAD ...mostly so that 16d6b7e835ffdcf9b894e79f933dd52348dedd0c (which reworks unaligned writes in Builder) and the stuff in https://github.com/haskell/bytestring/pull/631 can see wider testing. The less-terrible code for unaligned writes used in Builder on hosts not known to be ulaigned-friendly also takes less effort for GHC to compile, resulting in a metric decrease for T21839c on some platforms. The metric increase on T21839r is caused by the unrelated commit 750dac33465e7b59100698a330b44de7049a345c. It perhaps warrants further analysis and discussion (see #23822) but is not critical. Metric Decrease: T21839c Metric Increase: T21839r - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/merge_request_templates/Default.md - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CommonBlockElim.hs - compiler/GHC/Cmm/ContFlowOpt.hs - compiler/GHC/Cmm/Dataflow.hs - compiler/GHC/Cmm/Dataflow/Graph.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Lexer.x - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Utils.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f834cc8a9e15682a3ee161277fca165cc523fbd2...b2285cf4923c82c89134e2a3ba836bd18e41e955 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f834cc8a9e15682a3ee161277fca165cc523fbd2...b2285cf4923c82c89134e2a3ba836bd18e41e955 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Feb 1 17:43:00 2024 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Thu, 01 Feb 2024 12:43:00 -0500 Subject: [Git][ghc/ghc][wip/expand-do] Metric Increase 'compile_time/bytes allocated': Message-ID: <65bbd824c455a_1ad4f2767ace41577e6@gitlab.mail> Apoorv Ingle pushed to branch wip/expand-do at Glasgow Haskell Compiler / GHC Commits: 5e70372f by Apoorv Ingle at 2024-02-01T11:42:34-06:00 Metric Increase 'compile_time/bytes allocated': T9020 The testcase is a pathalogical example of a `do`-block with many statements that do nothing. Given that we are expanding the statements into function binds, we will have to bear a (small) 2% cost upfront in the compiler to unroll the statements. - - - - - 6 changed files: - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Tc/Gen/Do.hs - testsuite/tests/hpc/fork/hpc_fork.stdout - testsuite/tests/hpc/function/tough.stdout - testsuite/tests/hpc/function2/tough2.stdout - testsuite/tests/hpc/simple/hpc001.stdout Changes: ===================================== compiler/GHC/HsToCore/Ticks.hs ===================================== @@ -375,7 +375,9 @@ addTickLHsExpr e@(L pos e0) = do d <- getDensity case d of TickForBreakPoints | isGoodBreakExpr e0 -> tick_it - TickForCoverage | isGoodCoverageExpr e0 -> tick_it + TickForCoverage | XExpr (ExpandedThingTc OrigStmt{} _) <- e0 -- expansion ticks are handled separately + -> dont_tick_it + | otherwise -> tick_it TickCallSites | isCallSite e0 -> tick_it _other -> dont_tick_it where @@ -393,7 +395,7 @@ addTickLHsExprRHS e@(L pos e0) = do case d of TickForBreakPoints | HsLet{} <- e0 -> dont_tick_it | otherwise -> tick_it - TickForCoverage | isGoodCoverageExpr e0 -> tick_it + TickForCoverage -> tick_it TickCallSites | isCallSite e0 -> tick_it _other -> dont_tick_it where @@ -409,8 +411,7 @@ addTickLHsExprEvalInner :: LHsExpr GhcTc -> TM (LHsExpr GhcTc) addTickLHsExprEvalInner e = do d <- getDensity case d of - TickForCoverage | isGoodCoverageExpr (unLoc e) -> addTickLHsExpr e - | otherwise -> addTickLHsExprNever e + TickForCoverage -> addTickLHsExprNever e _otherwise -> addTickLHsExpr e -- | A let body is treated differently from addTickLHsExprEvalInner @@ -441,31 +442,9 @@ addTickLHsExprNever (L pos e0) = do -- General heuristic: expressions which are calls (do not denote -- values) are good break points. isGoodBreakExpr :: HsExpr GhcTc -> Bool -isGoodBreakExpr (XExpr (ExpandedThingTc thing e)) - | OrigStmt (L _ BodyStmt{}) <- thing - = False - | OrigStmt (L _ BindStmt{}) <- thing - = False - | OrigStmt (L _ LastStmt{}) <- thing - = True - | otherwise - = isCallSite e +isGoodBreakExpr (XExpr (ExpandedThingTc (OrigStmt{}) _)) = False isGoodBreakExpr e = isCallSite e --- Should coverage ticks be added to this expr? --- The general heuristic: Expanded `do`-stmts do not get --- the coverage ticks as they are accounted for in the expansions -isGoodCoverageExpr :: HsExpr GhcTc -> Bool -isGoodCoverageExpr (XExpr (ExpandedThingTc thing _)) - | OrigStmt (L _ BodyStmt{}) <- thing - = False - | OrigStmt (L _ BindStmt{}) <- thing - = False - | OrigStmt (L _ LetStmt{}) <- thing - = False -isGoodCoverageExpr _ = True - - isCallSite :: HsExpr GhcTc -> Bool isCallSite HsApp{} = True isCallSite HsAppType{} = True @@ -476,21 +455,18 @@ isCallSite (XExpr (ExpandedThingTc _ e)) -- NB: OpApp, SectionL, SectionR are all expanded out isCallSite _ = False -addTickLHsExprOptAlt :: Bool -> Bool {- is do expansion -} - -> LHsExpr GhcTc -> TM (LHsExpr GhcTc) -addTickLHsExprOptAlt oneOfMany isExpansion e@(L pos e0) - = if not (isExpansion) - then ifDensity TickForCoverage +addTickLHsExprOptAlt :: Bool -> LHsExpr GhcTc -> TM (LHsExpr GhcTc) +addTickLHsExprOptAlt oneOfMany e@(L pos e0) + = ifDensity TickForCoverage (allocTickBox (ExpBox oneOfMany) False False (locA pos) - $ addTickHsExpr e0) + $ addTickHsExpr e0) (addTickLHsExpr e) - else (addTickLHsExprNever e) addBinTickLHsExpr :: (Bool -> BoxLabel) -> LHsExpr GhcTc -> TM (LHsExpr GhcTc) -addBinTickLHsExpr boxLabel (L pos e0) +addBinTickLHsExpr boxLabel e@(L pos e0) = ifDensity TickForCoverage (allocBinTickBox boxLabel (locA pos) $ addTickHsExpr e0) - (addTickLHsExpr (L pos e0)) + (addTickLHsExpr e) -- ----------------------------------------------------------------------------- @@ -552,8 +528,8 @@ addTickHsExpr (HsCase x e mgs) = addTickHsExpr (HsIf x e1 e2 e3) = liftM3 (HsIf x) (addBinTickLHsExpr (BinBox CondBinBox) e1) - (addTickLHsExprOptAlt True False e2) - (addTickLHsExprOptAlt True False e3) + (addTickLHsExprOptAlt True e2) + (addTickLHsExprOptAlt True e3) addTickHsExpr (HsMultiIf ty alts) = do { let isOneOfMany = case alts of [_] -> False; _ -> True ; alts' <- mapM (traverse $ addTickGRHS isOneOfMany False False) alts @@ -613,9 +589,7 @@ addTickHsExpr (HsProc x pat cmdtop) = addTickHsExpr (XExpr (WrapExpr (HsWrap w e))) = liftM (XExpr . WrapExpr . HsWrap w) $ (addTickHsExpr e) -- Explicitly no tick on inside -addTickHsExpr (XExpr (ExpandedThingTc o e)) = - liftM (XExpr . ExpandedThingTc o) $ - addTickHsExpr e +addTickHsExpr (XExpr (ExpandedThingTc o e)) = addTickHsExpanded o e addTickHsExpr e@(XExpr (ConLikeTc {})) = return e -- We used to do a freeVar on a pat-syn builder, but actually @@ -636,6 +610,21 @@ addTickHsExpr (HsDo srcloc cxt (L l stmts)) ListComp -> Just $ BinBox QualBinBox _ -> Nothing +addTickHsExpanded :: HsThingRn -> HsExpr GhcTc -> TM (HsExpr GhcTc) +addTickHsExpanded o@(OrigStmt (L pos LastStmt{})) e + -- LastStmt always gets a tick for breakpoint and hpc coverage + = do d <- getDensity + case d of + TickForCoverage -> liftM (XExpr . ExpandedThingTc o) $ tick_it e + TickForBreakPoints -> liftM (XExpr . ExpandedThingTc o) $ tick_it e + _ -> liftM (XExpr . ExpandedThingTc o) $ addTickHsExpr e + where + tick_it e = unLoc <$> allocTickBox (ExpBox False) False False (locA pos) + (addTickHsExpr e) +addTickHsExpanded o e + = liftM (XExpr . ExpandedThingTc o) $ addTickHsExpr e + + addTickTupArg :: HsTupArg GhcTc -> TM (HsTupArg GhcTc) addTickTupArg (Present x e) = do { e' <- addTickLHsExpr e ; return (Present x e') } @@ -650,7 +639,7 @@ addTickMatchGroup is_lam mg@(MG { mg_alts = L l matches, mg_ext = ctxt }) = do matches' <- mapM (traverse (addTickMatch isOneOfMany is_lam isDoExp)) matches return $ mg { mg_alts = L l matches' } -addTickMatch :: Bool -> Bool -> Bool {-Is Do Expanion-} -> Match GhcTc (LHsExpr GhcTc) +addTickMatch :: Bool -> Bool -> Bool {-Is this Do Expansion-} -> Match GhcTc (LHsExpr GhcTc) -> TM (Match GhcTc (LHsExpr GhcTc)) addTickMatch isOneOfMany isLambda isDoExp match@(Match { m_pats = pats , m_grhss = gRHSs }) = @@ -680,10 +669,15 @@ addTickGRHSBody isOneOfMany isLambda isDoExp expr@(L pos e0) = do d <- getDensity case d of TickForBreakPoints - | XExpr (ExpandedThingTc thing _) <- e0 - , OrigStmt (L _ LastStmt{}) <- thing -> addTickLHsExprRHS expr - | isDoExp -> addTickLHsExprNever expr - TickForCoverage -> addTickLHsExprOptAlt isOneOfMany isDoExp expr + | isDoExp -- ticks for do-expansions are handled by `addTickHsExpanded` + -> addTickLHsExprNever expr + | otherwise + -> addTickLHsExprRHS expr + TickForCoverage + | isDoExp -- ticks for do-expansions are handled by `addTickHsExpanded` + -> addTickLHsExprNever expr + | otherwise + -> addTickLHsExprOptAlt isOneOfMany expr TickAllFunctions | isLambda -> addPathEntry "\\" $ allocTickBox (ExpBox False) True{-count-} False{-not top-} (locA pos) $ @@ -1093,6 +1087,7 @@ instance Monad TM where (r2,fv2,st2) -> (r2, fv1 `plusOccEnv` fv2, st2) + -- | Get the next HPC cost centre index for a given centre name getCCIndexM :: FastString -> TM CostCentreIndex getCCIndexM n = TM $ \_ st -> let (idx, is') = getCCIndex n $ @@ -1175,8 +1170,8 @@ allocTickBox boxLabel countEntries topOnly pos m = (fvs, e) <- getFreeVars m env <- getEnv tickish <- mkTickish boxLabel countEntries topOnly pos fvs (declPath env) - return (L (noAnnSrcSpan pos) (XExpr $ HsTick tickish $ L (noAnnSrcSpan pos) e)) - ) (do + return (L (noAnnSrcSpan pos) (XExpr $ HsTick tickish $ L (noAnnSrcSpan pos) e))) + (do e <- m return (L (noAnnSrcSpan pos) e) ) ===================================== compiler/GHC/Tc/Gen/Do.hs ===================================== @@ -92,7 +92,7 @@ expand_do_stmts _ [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_expr))] | NoSyntaxExprRn <- ret_expr -- Last statement is just body if we are not in ListComp context. See Syntax.Expr.LastStmt = do traceTc "expand_do_stmts last" (ppr ret_expr) - return $ mkExpandedStmtPopAt body_loc stmt body + return $ mkExpandedStmtPopAt loc stmt body | SyntaxExprRn ret <- ret_expr -- @@ -186,7 +186,8 @@ expand_do_stmts do_or_lc do_block :: LHsExpr GhcRn do_block = L loc $ HsDo noExtField do_or_lc do_stmts mfix_expr :: LHsExpr GhcRn - mfix_expr = genHsLamDoExp do_or_lc [ wrapGenSpan (LazyPat noExtField $ mkBigLHsVarPatTup all_ids) ] $ do_block + mfix_expr = genHsLamDoExp do_or_lc [ wrapGenSpan (LazyPat noExtField $ mkBigLHsVarPatTup all_ids) ] + $ do_block -- NB: LazyPat because we do not want to eagerly evaluate the pattern -- and potentially loop forever @@ -197,9 +198,9 @@ mk_failable_expr :: HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator G mk_failable_expr doFlav pat@(L loc _) expr fail_op = do { is_strict <- xoptM LangExt.Strict ; irrf_pat <- isIrrefutableHsPatRnTcM is_strict pat - ; traceTc "mk_fail_expr" (vcat [ text "pat:" <+> ppr pat - , text "isIrrefutable:" <+> ppr irrf_pat - ]) + ; traceTc "mk_failable_expr" (vcat [ text "pat:" <+> ppr pat + , text "isIrrefutable:" <+> ppr irrf_pat + ]) ; if irrf_pat -- don't wrap with fail block if -- the pattern is irrefutable ===================================== testsuite/tests/hpc/fork/hpc_fork.stdout ===================================== @@ -1,7 +1,7 @@ () - 60% expressions used (6/10) + 53% expressions used (7/13) 100% boolean coverage (0/0) 100% guards (0/0) 100% 'if' conditions (0/0) @@ -12,7 +12,7 @@ ---------- - 60% expressions used (6/10) + 53% expressions used (7/13) 100% boolean coverage (0/0) 100% guards (0/0) 100% 'if' conditions (0/0) @@ -67,10 +67,10 @@ table.dashboard { border-collapse: collapse ; border: solid 1px black } - + - +
moduleTop Level DefinitionsAlternativesExpressions
%covered / total%covered / total%covered / total
  module Main100%1/1
0/0 60%6/10
100%1/1
0/0 53%7/13
  Program Coverage Total100%1/1
0/0 60%6/10
100%1/1
0/0 53%7/13
Writing: hpc_index_fun.html